{-# Language PatternGuards, TemplateHaskell, Rank2Types, CPP #-}
module CabalCargs.CompilerArgs
( CompilerArgs(..)
, fromCmdArgs
, fromSpec
) where
import CabalCargs.Spec (Spec)
import qualified CabalCargs.Spec as Spec
import qualified CabalCargs.Args as A
import qualified CabalCargs.Fields as F
import qualified CabalCargs.BuildInfo as B
import qualified CabalLenses as CL
import Data.List (nub, foldl')
import Data.Maybe (maybeToList, listToMaybe)
import Control.Lens
import System.FilePath (takeDirectory, pathSeparator)
import qualified Filesystem.Path.CurrentOS as FP
#if __GLASGOW_HASKELL__ < 710
import Control.Applicative ((<$>))
#endif
data CompilerArgs = CompilerArgs
{ CompilerArgs -> [Error]
hsSourceDirs :: [FilePath]
, CompilerArgs -> [Error]
ghcOptions :: [String]
, CompilerArgs -> [Error]
defaultExtensions :: [String]
, CompilerArgs -> [Error]
defaultLanguage :: [String]
, CompilerArgs -> [Error]
cppOptions :: [String]
, CompilerArgs -> [Error]
cSources :: [FilePath]
, CompilerArgs -> [Error]
ccOptions :: [String]
, :: [FilePath]
, :: [String]
, CompilerArgs -> [Error]
ldOptions :: [String]
, CompilerArgs -> [Error]
includeDirs :: [FilePath]
, CompilerArgs -> [Error]
includes :: [String]
, CompilerArgs -> [Error]
buildDepends :: [String]
, CompilerArgs -> Maybe Error
packageDB :: Maybe FilePath
, CompilerArgs -> Maybe Error
rootDir :: Maybe FilePath
, CompilerArgs -> [Error]
autogenHsSourceDirs :: [FilePath]
, CompilerArgs -> [Error]
autogenIncludeDirs :: [FilePath]
, CompilerArgs -> [Error]
autogenIncludes :: [String]
, CompilerArgs -> Maybe Error
hdevtoolsSocket :: Maybe FilePath
}
deriving (Int -> CompilerArgs -> ShowS
[CompilerArgs] -> ShowS
CompilerArgs -> Error
(Int -> CompilerArgs -> ShowS)
-> (CompilerArgs -> Error)
-> ([CompilerArgs] -> ShowS)
-> Show CompilerArgs
forall a.
(Int -> a -> ShowS) -> (a -> Error) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CompilerArgs -> ShowS
showsPrec :: Int -> CompilerArgs -> ShowS
$cshow :: CompilerArgs -> Error
show :: CompilerArgs -> Error
$cshowList :: [CompilerArgs] -> ShowS
showList :: [CompilerArgs] -> ShowS
Show, CompilerArgs -> CompilerArgs -> Bool
(CompilerArgs -> CompilerArgs -> Bool)
-> (CompilerArgs -> CompilerArgs -> Bool) -> Eq CompilerArgs
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CompilerArgs -> CompilerArgs -> Bool
== :: CompilerArgs -> CompilerArgs -> Bool
$c/= :: CompilerArgs -> CompilerArgs -> Bool
/= :: CompilerArgs -> CompilerArgs -> Bool
Eq)
type Error = String
fromCmdArgs :: A.Args -> IO (Either Error CompilerArgs)
fromCmdArgs :: Args -> IO (Either Error CompilerArgs)
fromCmdArgs Args
args = (Spec -> CompilerArgs
fromSpec (Spec -> CompilerArgs)
-> Either Error Spec -> Either Error CompilerArgs
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) (Either Error Spec -> Either Error CompilerArgs)
-> IO (Either Error Spec) -> IO (Either Error CompilerArgs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Args -> IO (Either Error Spec)
Spec.fromCmdArgs Args
args
fromSpec :: Spec -> CompilerArgs
fromSpec :: Spec -> CompilerArgs
fromSpec Spec
spec = CompilerArgs -> CompilerArgs
changePaths (CompilerArgs -> CompilerArgs) -> CompilerArgs -> CompilerArgs
forall a b. (a -> b) -> a -> b
$ (CompilerArgs -> Section -> CompilerArgs)
-> CompilerArgs -> [Section] -> CompilerArgs
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' CompilerArgs -> Section -> CompilerArgs
collectFromSection CompilerArgs
defaultCompilerArgs (Spec -> [Section]
Spec.sections Spec
spec)
where
changePaths :: CompilerArgs -> CompilerArgs
changePaths CompilerArgs
cargs
| Spec -> Bool
Spec.relativePaths Spec
spec
= CompilerArgs
cargs CompilerArgs -> (CompilerArgs -> CompilerArgs) -> CompilerArgs
forall a b. a -> (a -> b) -> b
& ([Error] -> Identity [Error])
-> CompilerArgs -> Identity CompilerArgs
Lens' CompilerArgs [Error]
hsSourceDirsL (([Error] -> Identity [Error])
-> CompilerArgs -> Identity CompilerArgs)
-> ([Error] -> [Error]) -> CompilerArgs -> CompilerArgs
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ ShowS -> [Error] -> [Error]
forall a b. (a -> b) -> [a] -> [b]
map ShowS
stripCabalDir
CompilerArgs -> (CompilerArgs -> CompilerArgs) -> CompilerArgs
forall a b. a -> (a -> b) -> b
& ([Error] -> Identity [Error])
-> CompilerArgs -> Identity CompilerArgs
Lens' CompilerArgs [Error]
cSourcesL (([Error] -> Identity [Error])
-> CompilerArgs -> Identity CompilerArgs)
-> ([Error] -> [Error]) -> CompilerArgs -> CompilerArgs
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ ShowS -> [Error] -> [Error]
forall a b. (a -> b) -> [a] -> [b]
map ShowS
stripCabalDir
CompilerArgs -> (CompilerArgs -> CompilerArgs) -> CompilerArgs
forall a b. a -> (a -> b) -> b
& ([Error] -> Identity [Error])
-> CompilerArgs -> Identity CompilerArgs
Lens' CompilerArgs [Error]
extraLibDirsL (([Error] -> Identity [Error])
-> CompilerArgs -> Identity CompilerArgs)
-> ([Error] -> [Error]) -> CompilerArgs -> CompilerArgs
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ ShowS -> [Error] -> [Error]
forall a b. (a -> b) -> [a] -> [b]
map ShowS
stripCabalDir
CompilerArgs -> (CompilerArgs -> CompilerArgs) -> CompilerArgs
forall a b. a -> (a -> b) -> b
& ([Error] -> Identity [Error])
-> CompilerArgs -> Identity CompilerArgs
Lens' CompilerArgs [Error]
includeDirsL (([Error] -> Identity [Error])
-> CompilerArgs -> Identity CompilerArgs)
-> ([Error] -> [Error]) -> CompilerArgs -> CompilerArgs
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ ShowS -> [Error] -> [Error]
forall a b. (a -> b) -> [a] -> [b]
map ShowS
stripCabalDir
CompilerArgs -> (CompilerArgs -> CompilerArgs) -> CompilerArgs
forall a b. a -> (a -> b) -> b
& ([Error] -> Identity [Error])
-> CompilerArgs -> Identity CompilerArgs
Lens' CompilerArgs [Error]
autogenHsSourceDirsL (([Error] -> Identity [Error])
-> CompilerArgs -> Identity CompilerArgs)
-> ([Error] -> [Error]) -> CompilerArgs -> CompilerArgs
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ ShowS -> [Error] -> [Error]
forall a b. (a -> b) -> [a] -> [b]
map ShowS
stripCabalDir
CompilerArgs -> (CompilerArgs -> CompilerArgs) -> CompilerArgs
forall a b. a -> (a -> b) -> b
& ([Error] -> Identity [Error])
-> CompilerArgs -> Identity CompilerArgs
Lens' CompilerArgs [Error]
autogenIncludeDirsL (([Error] -> Identity [Error])
-> CompilerArgs -> Identity CompilerArgs)
-> ([Error] -> [Error]) -> CompilerArgs -> CompilerArgs
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ ShowS -> [Error] -> [Error]
forall a b. (a -> b) -> [a] -> [b]
map ShowS
stripCabalDir
CompilerArgs -> (CompilerArgs -> CompilerArgs) -> CompilerArgs
forall a b. a -> (a -> b) -> b
& (Maybe Error -> Identity (Maybe Error))
-> CompilerArgs -> Identity CompilerArgs
Lens' CompilerArgs (Maybe Error)
packageDBL ((Maybe Error -> Identity (Maybe Error))
-> CompilerArgs -> Identity CompilerArgs)
-> ((Error -> Identity Error)
-> Maybe Error -> Identity (Maybe Error))
-> (Error -> Identity Error)
-> CompilerArgs
-> Identity CompilerArgs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Error -> Identity Error) -> Maybe Error -> Identity (Maybe Error)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just ((Error -> Identity Error)
-> CompilerArgs -> Identity CompilerArgs)
-> ShowS -> CompilerArgs -> CompilerArgs
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ ShowS
stripCabalDir
CompilerArgs -> (CompilerArgs -> CompilerArgs) -> CompilerArgs
forall a b. a -> (a -> b) -> b
& (Maybe Error -> Identity (Maybe Error))
-> CompilerArgs -> Identity CompilerArgs
Lens' CompilerArgs (Maybe Error)
rootDirL ((Maybe Error -> Identity (Maybe Error))
-> CompilerArgs -> Identity CompilerArgs)
-> ((Error -> Identity Error)
-> Maybe Error -> Identity (Maybe Error))
-> (Error -> Identity Error)
-> CompilerArgs
-> Identity CompilerArgs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Error -> Identity Error) -> Maybe Error -> Identity (Maybe Error)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just ((Error -> Identity Error)
-> CompilerArgs -> Identity CompilerArgs)
-> Error -> CompilerArgs -> CompilerArgs
forall s t a b. ASetter s t a b -> b -> s -> t
.~ (Error
"." Error -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char
pathSeparator])
CompilerArgs -> (CompilerArgs -> CompilerArgs) -> CompilerArgs
forall a b. a -> (a -> b) -> b
& (Maybe Error -> Identity (Maybe Error))
-> CompilerArgs -> Identity CompilerArgs
Lens' CompilerArgs (Maybe Error)
hdevtoolsSocketL ((Maybe Error -> Identity (Maybe Error))
-> CompilerArgs -> Identity CompilerArgs)
-> ((Error -> Identity Error)
-> Maybe Error -> Identity (Maybe Error))
-> (Error -> Identity Error)
-> CompilerArgs
-> Identity CompilerArgs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Error -> Identity Error) -> Maybe Error -> Identity (Maybe Error)
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just ((Error -> Identity Error)
-> CompilerArgs -> Identity CompilerArgs)
-> ShowS -> CompilerArgs -> CompilerArgs
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ ShowS
stripCabalDir
| Bool
otherwise
= CompilerArgs
cargs
where
stripCabalDir :: ShowS
stripCabalDir Error
path = Error -> (FilePath -> Error) -> Maybe FilePath -> Error
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Error
path FilePath -> Error
FP.encodeString (FilePath -> FilePath -> Maybe FilePath
FP.stripPrefix FilePath
cabalDir (Error -> FilePath
FP.decodeString Error
path))
cabalDir :: FilePath
cabalDir = FilePath -> FilePath
FP.directory (FilePath -> FilePath) -> (Error -> FilePath) -> Error -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Error -> FilePath
FP.decodeString (Error -> FilePath) -> Error -> FilePath
forall a b. (a -> b) -> a -> b
$ Spec -> Error
Spec.cabalFile Spec
spec
collectFromSection :: CompilerArgs -> Section -> CompilerArgs
collectFromSection CompilerArgs
cargs Section
section =
(CompilerArgs -> Field -> CompilerArgs)
-> CompilerArgs -> [Field] -> CompilerArgs
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' CompilerArgs -> Field -> CompilerArgs
addCarg CompilerArgs
cargs (Spec -> [Field]
Spec.fields Spec
spec)
where
addCarg :: CompilerArgs -> Field -> CompilerArgs
addCarg CompilerArgs
cargs Field
F.Package_Db =
CompilerArgs
cargs CompilerArgs -> (CompilerArgs -> CompilerArgs) -> CompilerArgs
forall a b. a -> (a -> b) -> b
& (Maybe Error -> Identity (Maybe Error))
-> CompilerArgs -> Identity CompilerArgs
Lens' CompilerArgs (Maybe Error)
packageDBL ((Maybe Error -> Identity (Maybe Error))
-> CompilerArgs -> Identity CompilerArgs)
-> Maybe Error -> CompilerArgs -> CompilerArgs
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Spec -> Maybe Error
Spec.packageDB Spec
spec
addCarg CompilerArgs
cargs Field
F.Root_Dir =
CompilerArgs
cargs CompilerArgs -> (CompilerArgs -> CompilerArgs) -> CompilerArgs
forall a b. a -> (a -> b) -> b
& (Maybe Error -> Identity (Maybe Error))
-> CompilerArgs -> Identity CompilerArgs
Lens' CompilerArgs (Maybe Error)
rootDirL ((Maybe Error -> Identity (Maybe Error))
-> CompilerArgs -> Identity CompilerArgs)
-> Maybe Error -> CompilerArgs -> CompilerArgs
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Error -> Maybe Error
forall a. a -> Maybe a
Just (ShowS
takeDirectory ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ Spec -> Error
Spec.cabalFile Spec
spec)
addCarg CompilerArgs
cargs Field
F.Autogen_Hs_Source_Dirs
| Just Error
distDir <- Spec -> Maybe Error
Spec.distDir Spec
spec
= CompilerArgs
cargs CompilerArgs -> (CompilerArgs -> CompilerArgs) -> CompilerArgs
forall a b. a -> (a -> b) -> b
& ([Error] -> Identity [Error])
-> CompilerArgs -> Identity CompilerArgs
Lens' CompilerArgs [Error]
autogenHsSourceDirsL (([Error] -> Identity [Error])
-> CompilerArgs -> Identity CompilerArgs)
-> [Error] -> CompilerArgs -> CompilerArgs
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [Error
distDir Error -> ShowS
forall a. [a] -> [a] -> [a]
++ Error
"/build/autogen"]
| Bool
otherwise
= CompilerArgs
cargs
addCarg CompilerArgs
cargs Field
F.Autogen_Include_Dirs
| Just Error
distDir <- Spec -> Maybe Error
Spec.distDir Spec
spec
= CompilerArgs
cargs CompilerArgs -> (CompilerArgs -> CompilerArgs) -> CompilerArgs
forall a b. a -> (a -> b) -> b
& ([Error] -> Identity [Error])
-> CompilerArgs -> Identity CompilerArgs
Lens' CompilerArgs [Error]
autogenIncludeDirsL (([Error] -> Identity [Error])
-> CompilerArgs -> Identity CompilerArgs)
-> [Error] -> CompilerArgs -> CompilerArgs
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [Error
distDir Error -> ShowS
forall a. [a] -> [a] -> [a]
++ Error
"/build/autogen"]
| Bool
otherwise
= CompilerArgs
cargs
addCarg CompilerArgs
cargs Field
F.Autogen_Includes
| Just Error
_ <- Spec -> Maybe Error
Spec.distDir Spec
spec
= CompilerArgs
cargs CompilerArgs -> (CompilerArgs -> CompilerArgs) -> CompilerArgs
forall a b. a -> (a -> b) -> b
& ([Error] -> Identity [Error])
-> CompilerArgs -> Identity CompilerArgs
Lens' CompilerArgs [Error]
autogenIncludesL (([Error] -> Identity [Error])
-> CompilerArgs -> Identity CompilerArgs)
-> [Error] -> CompilerArgs -> CompilerArgs
forall s t a b. ASetter s t a b -> b -> s -> t
.~ [Error
"cabal_macros.h"]
| Bool
otherwise
= CompilerArgs
cargs
addCarg CompilerArgs
cargs Field
F.Hdevtools_Socket =
CompilerArgs
cargs CompilerArgs -> (CompilerArgs -> CompilerArgs) -> CompilerArgs
forall a b. a -> (a -> b) -> b
& (Maybe Error -> Identity (Maybe Error))
-> CompilerArgs -> Identity CompilerArgs
Lens' CompilerArgs (Maybe Error)
hdevtoolsSocketL ((Maybe Error -> Identity (Maybe Error))
-> CompilerArgs -> Identity CompilerArgs)
-> Maybe Error -> CompilerArgs -> CompilerArgs
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Error -> Maybe Error
forall a. a -> Maybe a
Just Error
".hdevtools.sock"
addCarg CompilerArgs
cargs Field
F.Build_Depends =
CompilerArgs
cargs CompilerArgs -> (CompilerArgs -> CompilerArgs) -> CompilerArgs
forall a b. a -> (a -> b) -> b
& ([Error] -> Identity [Error])
-> CompilerArgs -> Identity CompilerArgs
Lens' CompilerArgs [Error]
buildDependsL (([Error] -> Identity [Error])
-> CompilerArgs -> Identity CompilerArgs)
-> ([Error] -> [Error]) -> CompilerArgs -> CompilerArgs
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ [Error] -> [Error]
forall a. Eq a => [a] -> [a]
nub ([Error] -> [Error]) -> ([Error] -> [Error]) -> [Error] -> [Error]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Error] -> [Error] -> [Error]
forall a. [a] -> [a] -> [a]
++ [Error]
dependencies)
addCarg CompilerArgs
cargs Field
field =
CompilerArgs
cargs CompilerArgs -> (CompilerArgs -> CompilerArgs) -> CompilerArgs
forall a b. a -> (a -> b) -> b
& Field -> Lens' CompilerArgs [Error]
fieldL Field
field (([Error] -> Identity [Error])
-> CompilerArgs -> Identity CompilerArgs)
-> ([Error] -> [Error]) -> CompilerArgs -> CompilerArgs
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ [Error] -> [Error]
forall a. Eq a => [a] -> [a]
nub ([Error] -> [Error]) -> ([Error] -> [Error]) -> [Error] -> [Error]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Error] -> [Error] -> [Error]
forall a. [a] -> [a] -> [a]
++ [Error]
buildInfoFields)
where
buildInfoFields :: [Error]
buildInfoFields = (BuildInfo -> [Error]) -> [BuildInfo] -> [Error]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (BuildInfo -> Getting [Error] BuildInfo [Error] -> [Error]
forall s a. s -> Getting a s a -> a
^. Field -> Traversal' BuildInfo [Error]
B.field Field
field) [BuildInfo]
buildInfos
dependencies :: [Unwrapped PackageName]
dependencies = GenericPackageDescription
pkgDescrp GenericPackageDescription
-> Getting
(Endo [Unwrapped PackageName])
GenericPackageDescription
(Unwrapped PackageName)
-> [Unwrapped PackageName]
forall s a. s -> Getting (Endo [a]) s a -> [a]
^.. CondVars
-> Section -> Traversal' GenericPackageDescription Dependency
CL.dependencyIf CondVars
condVars Section
section ((Dependency -> Const (Endo [Unwrapped PackageName]) Dependency)
-> GenericPackageDescription
-> Const (Endo [Unwrapped PackageName]) GenericPackageDescription)
-> ((Unwrapped PackageName
-> Const (Endo [Unwrapped PackageName]) (Unwrapped PackageName))
-> Dependency -> Const (Endo [Unwrapped PackageName]) Dependency)
-> Getting
(Endo [Unwrapped PackageName])
GenericPackageDescription
(Unwrapped PackageName)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PackageName -> Const (Endo [Unwrapped PackageName]) PackageName)
-> Dependency -> Const (Endo [Unwrapped PackageName]) Dependency
Lens' Dependency PackageName
CL.packageName ((PackageName -> Const (Endo [Unwrapped PackageName]) PackageName)
-> Dependency -> Const (Endo [Unwrapped PackageName]) Dependency)
-> ((Unwrapped PackageName
-> Const (Endo [Unwrapped PackageName]) (Unwrapped PackageName))
-> PackageName -> Const (Endo [Unwrapped PackageName]) PackageName)
-> (Unwrapped PackageName
-> Const (Endo [Unwrapped PackageName]) (Unwrapped PackageName))
-> Dependency
-> Const (Endo [Unwrapped PackageName]) Dependency
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Unwrapped PackageName
-> Const (Endo [Unwrapped PackageName]) (Unwrapped PackageName))
-> PackageName -> Const (Endo [Unwrapped PackageName]) PackageName
forall s t. Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t)
Iso
PackageName
PackageName
(Unwrapped PackageName)
(Unwrapped PackageName)
_Wrapped
buildInfos :: [BuildInfo]
buildInfos = GenericPackageDescription
pkgDescrp GenericPackageDescription
-> Getting (Endo [BuildInfo]) GenericPackageDescription BuildInfo
-> [BuildInfo]
forall s a. s -> Getting (Endo [a]) s a -> [a]
^.. CondVars
-> Section -> Traversal' GenericPackageDescription BuildInfo
CL.buildInfoIf CondVars
condVars Section
section
pkgDescrp :: GenericPackageDescription
pkgDescrp = Spec -> GenericPackageDescription
Spec.pkgDescrp Spec
spec
condVars :: CondVars
condVars = Spec -> CondVars
Spec.condVars Spec
spec
fieldL :: F.Field -> Lens' CompilerArgs [String]
fieldL :: Field -> Lens' CompilerArgs [Error]
fieldL Field
F.Hs_Source_Dirs = ([Error] -> f [Error]) -> CompilerArgs -> f CompilerArgs
Lens' CompilerArgs [Error]
hsSourceDirsL
fieldL Field
F.Ghc_Options = ([Error] -> f [Error]) -> CompilerArgs -> f CompilerArgs
Lens' CompilerArgs [Error]
ghcOptionsL
fieldL Field
F.Default_Extensions = ([Error] -> f [Error]) -> CompilerArgs -> f CompilerArgs
Lens' CompilerArgs [Error]
defaultExtensionsL
fieldL Field
F.Default_Language = ([Error] -> f [Error]) -> CompilerArgs -> f CompilerArgs
Lens' CompilerArgs [Error]
defaultLanguageL
fieldL Field
F.Cpp_Options = ([Error] -> f [Error]) -> CompilerArgs -> f CompilerArgs
Lens' CompilerArgs [Error]
cppOptionsL
fieldL Field
F.C_Sources = ([Error] -> f [Error]) -> CompilerArgs -> f CompilerArgs
Lens' CompilerArgs [Error]
cSourcesL
fieldL Field
F.Cc_Options = ([Error] -> f [Error]) -> CompilerArgs -> f CompilerArgs
Lens' CompilerArgs [Error]
ccOptionsL
fieldL Field
F.Extra_Lib_Dirs = ([Error] -> f [Error]) -> CompilerArgs -> f CompilerArgs
Lens' CompilerArgs [Error]
extraLibDirsL
fieldL Field
F.Extra_Libraries = ([Error] -> f [Error]) -> CompilerArgs -> f CompilerArgs
Lens' CompilerArgs [Error]
extraLibrariesL
fieldL Field
F.Ld_Options = ([Error] -> f [Error]) -> CompilerArgs -> f CompilerArgs
Lens' CompilerArgs [Error]
ldOptionsL
fieldL Field
F.Include_Dirs = ([Error] -> f [Error]) -> CompilerArgs -> f CompilerArgs
Lens' CompilerArgs [Error]
includeDirsL
fieldL Field
F.Includes = ([Error] -> f [Error]) -> CompilerArgs -> f CompilerArgs
Lens' CompilerArgs [Error]
includesL
fieldL Field
F.Build_Depends = ([Error] -> f [Error]) -> CompilerArgs -> f CompilerArgs
Lens' CompilerArgs [Error]
buildDependsL
fieldL Field
F.Package_Db = (Maybe Error -> f (Maybe Error)) -> CompilerArgs -> f CompilerArgs
Lens' CompilerArgs (Maybe Error)
packageDBL ((Maybe Error -> f (Maybe Error))
-> CompilerArgs -> f CompilerArgs)
-> (([Error] -> f [Error]) -> Maybe Error -> f (Maybe Error))
-> ([Error] -> f [Error])
-> CompilerArgs
-> f CompilerArgs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Error] -> f [Error]) -> Maybe Error -> f (Maybe Error)
forall a (p :: * -> * -> *) (f :: * -> *).
(Profunctor p, Functor f) =>
p [a] (f [a]) -> p (Maybe a) (f (Maybe a))
maybeToListL
fieldL Field
F.Root_Dir = (Maybe Error -> f (Maybe Error)) -> CompilerArgs -> f CompilerArgs
Lens' CompilerArgs (Maybe Error)
rootDirL ((Maybe Error -> f (Maybe Error))
-> CompilerArgs -> f CompilerArgs)
-> (([Error] -> f [Error]) -> Maybe Error -> f (Maybe Error))
-> ([Error] -> f [Error])
-> CompilerArgs
-> f CompilerArgs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Error] -> f [Error]) -> Maybe Error -> f (Maybe Error)
forall a (p :: * -> * -> *) (f :: * -> *).
(Profunctor p, Functor f) =>
p [a] (f [a]) -> p (Maybe a) (f (Maybe a))
maybeToListL
fieldL Field
F.Autogen_Hs_Source_Dirs = ([Error] -> f [Error]) -> CompilerArgs -> f CompilerArgs
Lens' CompilerArgs [Error]
autogenHsSourceDirsL
fieldL Field
F.Autogen_Include_Dirs = ([Error] -> f [Error]) -> CompilerArgs -> f CompilerArgs
Lens' CompilerArgs [Error]
autogenIncludeDirsL
fieldL Field
F.Autogen_Includes = ([Error] -> f [Error]) -> CompilerArgs -> f CompilerArgs
Lens' CompilerArgs [Error]
autogenIncludesL
fieldL Field
F.Hdevtools_Socket = (Maybe Error -> f (Maybe Error)) -> CompilerArgs -> f CompilerArgs
Lens' CompilerArgs (Maybe Error)
hdevtoolsSocketL ((Maybe Error -> f (Maybe Error))
-> CompilerArgs -> f CompilerArgs)
-> (([Error] -> f [Error]) -> Maybe Error -> f (Maybe Error))
-> ([Error] -> f [Error])
-> CompilerArgs
-> f CompilerArgs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Error] -> f [Error]) -> Maybe Error -> f (Maybe Error)
forall a (p :: * -> * -> *) (f :: * -> *).
(Profunctor p, Functor f) =>
p [a] (f [a]) -> p (Maybe a) (f (Maybe a))
maybeToListL
maybeToListL :: Iso' (Maybe a) [a]
maybeToListL :: forall a (p :: * -> * -> *) (f :: * -> *).
(Profunctor p, Functor f) =>
p [a] (f [a]) -> p (Maybe a) (f (Maybe a))
maybeToListL = (Maybe a -> [a])
-> ([a] -> Maybe a) -> Iso (Maybe a) (Maybe a) [a] [a]
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Maybe a -> [a]
forall a. Maybe a -> [a]
maybeToList [a] -> Maybe a
forall a. [a] -> Maybe a
listToMaybe
defaultCompilerArgs :: CompilerArgs
defaultCompilerArgs :: CompilerArgs
defaultCompilerArgs = CompilerArgs
{ hsSourceDirs :: [Error]
hsSourceDirs = []
, ghcOptions :: [Error]
ghcOptions = []
, defaultExtensions :: [Error]
defaultExtensions = []
, defaultLanguage :: [Error]
defaultLanguage = []
, cppOptions :: [Error]
cppOptions = []
, cSources :: [Error]
cSources = []
, ccOptions :: [Error]
ccOptions = []
, extraLibDirs :: [Error]
extraLibDirs = []
, extraLibraries :: [Error]
extraLibraries = []
, ldOptions :: [Error]
ldOptions = []
, includeDirs :: [Error]
includeDirs = []
, includes :: [Error]
includes = []
, buildDepends :: [Error]
buildDepends = []
, packageDB :: Maybe Error
packageDB = Maybe Error
forall a. Maybe a
Nothing
, autogenHsSourceDirs :: [Error]
autogenHsSourceDirs = []
, autogenIncludeDirs :: [Error]
autogenIncludeDirs = []
, autogenIncludes :: [Error]
autogenIncludes = []
, hdevtoolsSocket :: Maybe Error
hdevtoolsSocket = Maybe Error
forall a. Maybe a
Nothing
, rootDir :: Maybe Error
rootDir = Maybe Error
forall a. Maybe a
Nothing
}