Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
This does a merger of V04 and V10
Effectivelly this provides the latest
config.
Synopsis
- data PortSettings = PortSettings {}
- data TLSConfig = TLSConfig !Settings !FilePath !FilePath (Maybe Config)
- data BundleConfig = BundleConfig {
- bconfigStanzas :: !(Vector (Stanza ()))
- bconfigPlugins :: !Object
- data WebAppConfig port = WebAppConfig {
- waconfigExec :: !FilePath
- waconfigArgs :: !(Vector Text)
- waconfigEnvironment :: !(Map Text Text)
- waconfigApprootHost :: !Host
- waconfigHosts :: !(Set Host)
- waconfigSsl :: !SSLConfig
- waconfigPort :: !port
- waconfigForwardEnv :: !(Set Text)
- waconfigTimeout :: !(Maybe Int)
- waconfigEnsureAliveTimeout :: !(Maybe Int)
- data RedirectConfig = RedirectConfig {
- redirconfigHosts :: !(Set Host)
- redirconfigStatus :: !Int
- redirconfigActions :: !(Vector RedirectAction)
- redirconfigSsl :: !SSLConfig
- data StaticFilesConfig = StaticFilesConfig {
- sfconfigRoot :: !FilePath
- sfconfigHosts :: !(Set Host)
- sfconfigListings :: !Bool
- sfconfigMiddleware :: ![MiddlewareConfig]
- sfconfigTimeout :: !(Maybe Int)
- sfconfigSsl :: !SSLConfig
- data KeterConfig = KeterConfig {
- kconfigDir :: FilePath
- kconfigPortPool :: PortSettings
- kconfigListeners :: !(NonEmptyVector ListeningPort)
- kconfigSetuid :: Maybe Text
- kconfigBuiltinStanzas :: !(Vector (Stanza ()))
- kconfigIpFromHeader :: Bool
- kconfigExternalHttpPort :: !Int
- kconfigExternalHttpsPort :: !Int
- kconfigEnvironment :: !(Map Text Text)
- kconfigConnectionTimeBound :: !Int
- kconfigCliPort :: !(Maybe Port)
- kconfigUnknownHostResponse :: !(Maybe FilePath)
- kconfigMissingHostResponse :: !(Maybe FilePath)
- kconfigProxyException :: !(Maybe FilePath)
- kconfigRotateLogs :: !Bool
- kconfigHealthcheckPath :: !(Maybe Text)
- data Stanza port = Stanza (StanzaRaw port) RequiresSecure
- data StanzaRaw port
- type ProxyAction = (ProxyActionRaw, RequiresSecure)
- data ProxyActionRaw
- data RedirectDest
- data RedirectAction = RedirectAction !SourcePath !RedirectDest
- data SourcePath
- = SPAny
- | SPSpecific !Text
- data ListeningPort
- = LPSecure !HostPreference !Port !FilePath !(Vector FilePath) !FilePath !Bool
- | LPInsecure !HostPreference !Port
- data AppInput
- data BackgroundConfig = BackgroundConfig {
- bgconfigExec :: !FilePath
- bgconfigArgs :: !(Vector Text)
- bgconfigEnvironment :: !(Map Text Text)
- bgconfigRestartCount :: !RestartCount
- bgconfigRestartDelaySeconds :: !Word
- bgconfigForwardEnv :: !(Set Text)
- data RestartCount
- type RequiresSecure = Bool
Documentation
data PortSettings Source #
Controls execution of the nginx thread. Follows the settings type pattern. See: http://www.yesodweb.com/book/settings-types.
Instances
FromJSON PortSettings Source # | |
Defined in Keter.Config.V04 parseJSON :: Value -> Parser PortSettings # parseJSONList :: Value -> Parser [PortSettings] # |
Instances
ParseYamlFile TLSConfig Source # | |
Defined in Keter.Config.V04 |
data BundleConfig Source #
BundleConfig | |
|
Instances
ToJSON BundleConfig Source # | |
Defined in Keter.Config.V10 toJSON :: BundleConfig -> Value # toEncoding :: BundleConfig -> Encoding # toJSONList :: [BundleConfig] -> Value # toEncodingList :: [BundleConfig] -> Encoding # omitField :: BundleConfig -> Bool # | |
Show BundleConfig Source # | |
Defined in Keter.Config.V10 showsPrec :: Int -> BundleConfig -> ShowS # show :: BundleConfig -> String # showList :: [BundleConfig] -> ShowS # | |
ToCurrent BundleConfig Source # | |
Defined in Keter.Config.V10 type Previous BundleConfig Source # | |
ParseYamlFile BundleConfig Source # | |
Defined in Keter.Config.V10 parseYamlFile :: BaseDir -> Value -> Parser BundleConfig Source # | |
type Previous BundleConfig Source # | |
Defined in Keter.Config.V10 |
data WebAppConfig port Source #
WebAppConfig | |
|
Instances
ToJSON (WebAppConfig ()) Source # | |
Defined in Keter.Config.V10 toJSON :: WebAppConfig () -> Value # toEncoding :: WebAppConfig () -> Encoding # toJSONList :: [WebAppConfig ()] -> Value # toEncodingList :: [WebAppConfig ()] -> Encoding # omitField :: WebAppConfig () -> Bool # | |
Show port => Show (WebAppConfig port) Source # | |
Defined in Keter.Config.V10 showsPrec :: Int -> WebAppConfig port -> ShowS # show :: WebAppConfig port -> String # showList :: [WebAppConfig port] -> ShowS # | |
ToCurrent (WebAppConfig ()) Source # | |
Defined in Keter.Config.V10 type Previous (WebAppConfig ()) Source # toCurrent :: Previous (WebAppConfig ()) -> WebAppConfig () Source # | |
ParseYamlFile (WebAppConfig ()) Source # | |
Defined in Keter.Config.V10 parseYamlFile :: BaseDir -> Value -> Parser (WebAppConfig ()) Source # | |
type Previous (WebAppConfig ()) Source # | |
Defined in Keter.Config.V10 |
data RedirectConfig Source #
RedirectConfig | |
|
Instances
ToJSON RedirectConfig Source # | |
Defined in Keter.Config.V10 toJSON :: RedirectConfig -> Value # toEncoding :: RedirectConfig -> Encoding # toJSONList :: [RedirectConfig] -> Value # toEncodingList :: [RedirectConfig] -> Encoding # omitField :: RedirectConfig -> Bool # | |
Show RedirectConfig Source # | |
Defined in Keter.Config.V10 showsPrec :: Int -> RedirectConfig -> ShowS # show :: RedirectConfig -> String # showList :: [RedirectConfig] -> ShowS # | |
ToCurrent RedirectConfig Source # | |
Defined in Keter.Config.V10 type Previous RedirectConfig Source # | |
ParseYamlFile RedirectConfig Source # | |
Defined in Keter.Config.V10 parseYamlFile :: BaseDir -> Value -> Parser RedirectConfig Source # | |
type Previous RedirectConfig Source # | |
Defined in Keter.Config.V10 |
data StaticFilesConfig Source #
StaticFilesConfig | |
|
Instances
ToJSON StaticFilesConfig Source # | |
Defined in Keter.Config.V10 toJSON :: StaticFilesConfig -> Value # toEncoding :: StaticFilesConfig -> Encoding # toJSONList :: [StaticFilesConfig] -> Value # toEncodingList :: [StaticFilesConfig] -> Encoding # omitField :: StaticFilesConfig -> Bool # | |
Show StaticFilesConfig Source # | |
Defined in Keter.Config.V10 showsPrec :: Int -> StaticFilesConfig -> ShowS # show :: StaticFilesConfig -> String # showList :: [StaticFilesConfig] -> ShowS # | |
ToCurrent StaticFilesConfig Source # | |
Defined in Keter.Config.V10 type Previous StaticFilesConfig Source # | |
ParseYamlFile StaticFilesConfig Source # | |
Defined in Keter.Config.V10 parseYamlFile :: BaseDir -> Value -> Parser StaticFilesConfig Source # | |
type Previous StaticFilesConfig Source # | |
Defined in Keter.Config.V10 |
data KeterConfig Source #
KeterConfig | |
|
Instances
ToCurrent KeterConfig Source # | |
Defined in Keter.Config.V10 type Previous KeterConfig Source # | |
ParseYamlFile KeterConfig Source # | |
Defined in Keter.Config.V10 parseYamlFile :: BaseDir -> Value -> Parser KeterConfig Source # | |
type Previous KeterConfig Source # | |
Defined in Keter.Config.V10 |
Stanza (StanzaRaw port) RequiresSecure |
type ProxyAction = (ProxyActionRaw, RequiresSecure) Source #
data ProxyActionRaw Source #
An action to be performed for a requested hostname.
This datatype is very similar to Stanza, but is necessarily separate since:
- Webapps will be assigned ports.
- Not all stanzas have an associated proxy action.
PAPort Port !(Maybe Int) | |
PAStatic StaticFilesConfig | |
PARedirect RedirectConfig | |
PAReverseProxy ReverseProxyConfig ![MiddlewareConfig] !(Maybe Int) |
Instances
Show ProxyActionRaw Source # | |
Defined in Keter.Config.V10 showsPrec :: Int -> ProxyActionRaw -> ShowS # show :: ProxyActionRaw -> String # showList :: [ProxyActionRaw] -> ShowS # |
data RedirectDest Source #
Instances
FromJSON RedirectDest Source # | |
Defined in Keter.Config.V10 parseJSON :: Value -> Parser RedirectDest # parseJSONList :: Value -> Parser [RedirectDest] # | |
ToJSON RedirectDest Source # | |
Defined in Keter.Config.V10 toJSON :: RedirectDest -> Value # toEncoding :: RedirectDest -> Encoding # toJSONList :: [RedirectDest] -> Value # toEncodingList :: [RedirectDest] -> Encoding # omitField :: RedirectDest -> Bool # | |
Show RedirectDest Source # | |
Defined in Keter.Config.V10 showsPrec :: Int -> RedirectDest -> ShowS # show :: RedirectDest -> String # showList :: [RedirectDest] -> ShowS # |
data RedirectAction Source #
Instances
FromJSON RedirectAction Source # | |
Defined in Keter.Config.V10 parseJSON :: Value -> Parser RedirectAction # parseJSONList :: Value -> Parser [RedirectAction] # | |
ToJSON RedirectAction Source # | |
Defined in Keter.Config.V10 toJSON :: RedirectAction -> Value # toEncoding :: RedirectAction -> Encoding # toJSONList :: [RedirectAction] -> Value # toEncodingList :: [RedirectAction] -> Encoding # omitField :: RedirectAction -> Bool # | |
Show RedirectAction Source # | |
Defined in Keter.Config.V10 showsPrec :: Int -> RedirectAction -> ShowS # show :: RedirectAction -> String # showList :: [RedirectAction] -> ShowS # |
data SourcePath Source #
Instances
Show SourcePath Source # | |
Defined in Keter.Config.V10 showsPrec :: Int -> SourcePath -> ShowS # show :: SourcePath -> String # showList :: [SourcePath] -> ShowS # |
data ListeningPort Source #
LPSecure !HostPreference !Port !FilePath !(Vector FilePath) !FilePath !Bool | |
LPInsecure !HostPreference !Port |
Instances
ParseYamlFile ListeningPort Source # | |
Defined in Keter.Config.V10 parseYamlFile :: BaseDir -> Value -> Parser ListeningPort Source # |
data BackgroundConfig Source #
BackgroundConfig | |
|
Instances
ToJSON BackgroundConfig Source # | |
Defined in Keter.Config.V10 toJSON :: BackgroundConfig -> Value # toEncoding :: BackgroundConfig -> Encoding # toJSONList :: [BackgroundConfig] -> Value # toEncodingList :: [BackgroundConfig] -> Encoding # omitField :: BackgroundConfig -> Bool # | |
Show BackgroundConfig Source # | |
Defined in Keter.Config.V10 showsPrec :: Int -> BackgroundConfig -> ShowS # show :: BackgroundConfig -> String # showList :: [BackgroundConfig] -> ShowS # | |
ParseYamlFile BackgroundConfig Source # | |
Defined in Keter.Config.V10 parseYamlFile :: BaseDir -> Value -> Parser BackgroundConfig Source # |
data RestartCount Source #
Instances
FromJSON RestartCount Source # | |
Defined in Keter.Config.V10 parseJSON :: Value -> Parser RestartCount # parseJSONList :: Value -> Parser [RestartCount] # | |
Show RestartCount Source # | |
Defined in Keter.Config.V10 showsPrec :: Int -> RestartCount -> ShowS # show :: RestartCount -> String # showList :: [RestartCount] -> ShowS # |
type RequiresSecure = Bool Source #
Whether we should force redirect to HTTPS routes.