module FFICXX.Generate.Config where
import FFICXX.Generate.Type.Cabal ( Cabal )
import FFICXX.Generate.Type.Class ( Class, TopLevel )
import FFICXX.Generate.Type.Config ( ModuleUnitMap(..) )
import FFICXX.Generate.Type.Module ( TemplateClassImportHeader )
data FFICXXConfig = FFICXXConfig {
FFICXXConfig -> FilePath
fficxxconfig_workingDir :: FilePath
, FFICXXConfig -> FilePath
fficxxconfig_installBaseDir :: FilePath
, FFICXXConfig -> FilePath
fficxxconfig_staticFileDir :: FilePath
} deriving Int -> FFICXXConfig -> ShowS
[FFICXXConfig] -> ShowS
FFICXXConfig -> FilePath
(Int -> FFICXXConfig -> ShowS)
-> (FFICXXConfig -> FilePath)
-> ([FFICXXConfig] -> ShowS)
-> Show FFICXXConfig
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [FFICXXConfig] -> ShowS
$cshowList :: [FFICXXConfig] -> ShowS
show :: FFICXXConfig -> FilePath
$cshow :: FFICXXConfig -> FilePath
showsPrec :: Int -> FFICXXConfig -> ShowS
$cshowsPrec :: Int -> FFICXXConfig -> ShowS
Show
data SimpleBuilderConfig =
SimpleBuilderConfig {
SimpleBuilderConfig -> FilePath
sbcTopModule :: String
, SimpleBuilderConfig -> ModuleUnitMap
sbcModUnitMap :: ModuleUnitMap
, SimpleBuilderConfig -> Cabal
sbcCabal :: Cabal
, SimpleBuilderConfig -> [Class]
sbcClasses :: [Class]
, SimpleBuilderConfig -> [TopLevel]
sbcTopLevels :: [TopLevel]
, SimpleBuilderConfig -> [TemplateClassImportHeader]
sbcTemplates :: [TemplateClassImportHeader]
, :: [String]
, :: [(String,[String])]
, SimpleBuilderConfig -> [FilePath]
sbcStaticFiles :: [String]
}