| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Keter.Types.V10
Synopsis
- data BundleConfig = BundleConfig {- bconfigStanzas :: !(Vector (Stanza ()))
- bconfigPlugins :: !Object
 
- data ListeningPort- = LPSecure !HostPreference !Port !FilePath !(Vector FilePath) !FilePath !Bool
- | LPInsecure !HostPreference !Port
 
- 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)
 
- type RequiresSecure = Bool
- data Stanza port = Stanza (StanzaRaw port) RequiresSecure
- data StanzaRaw port
- data ProxyActionRaw
- type ProxyAction = (ProxyActionRaw, RequiresSecure)
- addRequiresSecure :: ToJSON a => Bool -> a -> Value
- addStanzaType :: ToJSON a => Value -> a -> Value
- data StaticFilesConfig = StaticFilesConfig {- sfconfigRoot :: !FilePath
- sfconfigHosts :: !(Set Host)
- sfconfigListings :: !Bool
- sfconfigMiddleware :: ![MiddlewareConfig]
- sfconfigTimeout :: !(Maybe Int)
- sfconfigSsl :: !SSLConfig
 
- data RedirectConfig = RedirectConfig {- redirconfigHosts :: !(Set Host)
- redirconfigStatus :: !Int
- redirconfigActions :: !(Vector RedirectAction)
- redirconfigSsl :: !SSLConfig
 
- data RedirectAction = RedirectAction !SourcePath !RedirectDest
- data SourcePath- = SPAny
- | SPSpecific !Text
 
- data RedirectDest
- type IsSecure = Bool
- 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 AppInput
- data BackgroundConfig = BackgroundConfig {- bgconfigExec :: !FilePath
- bgconfigArgs :: !(Vector Text)
- bgconfigEnvironment :: !(Map Text Text)
- bgconfigRestartCount :: !RestartCount
- bgconfigRestartDelaySeconds :: !Word
- bgconfigForwardEnv :: !(Set Text)
 
- data RestartCount
Documentation
data BundleConfig Source #
Constructors
| BundleConfig | |
| Fields 
 | |
Instances
| Show BundleConfig Source # | |
| Defined in Keter.Types.V10 Methods showsPrec :: Int -> BundleConfig -> ShowS # show :: BundleConfig -> String # showList :: [BundleConfig] -> ShowS # | |
| ToJSON BundleConfig Source # | |
| Defined in Keter.Types.V10 Methods toJSON :: BundleConfig -> Value # toEncoding :: BundleConfig -> Encoding # toJSONList :: [BundleConfig] -> Value # toEncodingList :: [BundleConfig] -> Encoding # | |
| ParseYamlFile BundleConfig Source # | |
| Defined in Keter.Types.V10 Methods parseYamlFile :: BaseDir -> Value -> Parser BundleConfig Source # | |
| ToCurrent BundleConfig Source # | |
| type Previous BundleConfig Source # | |
| Defined in Keter.Types.V10 | |
data ListeningPort Source #
Constructors
| LPSecure !HostPreference !Port !FilePath !(Vector FilePath) !FilePath !Bool | |
| LPInsecure !HostPreference !Port | 
Instances
| ParseYamlFile ListeningPort Source # | |
| Defined in Keter.Types.V10 Methods parseYamlFile :: BaseDir -> Value -> Parser ListeningPort Source # | |
data KeterConfig Source #
Constructors
| KeterConfig | |
| Fields 
 | |
Instances
| Default KeterConfig Source # | |
| Defined in Keter.Types.V10 Methods def :: KeterConfig # | |
| ParseYamlFile KeterConfig Source # | |
| Defined in Keter.Types.V10 Methods parseYamlFile :: BaseDir -> Value -> Parser KeterConfig Source # | |
| ToCurrent KeterConfig Source # | |
| type Previous KeterConfig Source # | |
| Defined in Keter.Types.V10 | |
type RequiresSecure = Bool Source #
Whether we should force redirect to HTTPS routes.
Constructors
| Stanza (StanzaRaw port) RequiresSecure | 
Instances
| Show port => Show (Stanza port) Source # | |
| ToJSON (Stanza ()) Source # | |
| Defined in Keter.Types.V10 | |
| ParseYamlFile (Stanza ()) Source # | |
| Defined in Keter.Types.V10 | |
Constructors
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.
Constructors
| PAPort Port !(Maybe Int) | |
| PAStatic StaticFilesConfig | |
| PARedirect RedirectConfig | |
| PAReverseProxy ReverseProxyConfig ![MiddlewareConfig] !(Maybe Int) | 
Instances
| Show ProxyActionRaw Source # | |
| Defined in Keter.Types.V10 Methods showsPrec :: Int -> ProxyActionRaw -> ShowS # show :: ProxyActionRaw -> String # showList :: [ProxyActionRaw] -> ShowS # | |
type ProxyAction = (ProxyActionRaw, RequiresSecure) Source #
data StaticFilesConfig Source #
Constructors
| StaticFilesConfig | |
| Fields 
 | |
Instances
| Show StaticFilesConfig Source # | |
| Defined in Keter.Types.V10 Methods showsPrec :: Int -> StaticFilesConfig -> ShowS # show :: StaticFilesConfig -> String # showList :: [StaticFilesConfig] -> ShowS # | |
| ToJSON StaticFilesConfig Source # | |
| Defined in Keter.Types.V10 Methods toJSON :: StaticFilesConfig -> Value # toEncoding :: StaticFilesConfig -> Encoding # toJSONList :: [StaticFilesConfig] -> Value # toEncodingList :: [StaticFilesConfig] -> Encoding # | |
| ParseYamlFile StaticFilesConfig Source # | |
| Defined in Keter.Types.V10 Methods parseYamlFile :: BaseDir -> Value -> Parser StaticFilesConfig Source # | |
| ToCurrent StaticFilesConfig Source # | |
| Defined in Keter.Types.V10 Associated Types type Previous StaticFilesConfig Source # Methods toCurrent :: Previous StaticFilesConfig -> StaticFilesConfig Source # | |
| type Previous StaticFilesConfig Source # | |
| Defined in Keter.Types.V10 | |
data RedirectConfig Source #
Constructors
| RedirectConfig | |
| Fields 
 | |
Instances
| Show RedirectConfig Source # | |
| Defined in Keter.Types.V10 Methods showsPrec :: Int -> RedirectConfig -> ShowS # show :: RedirectConfig -> String # showList :: [RedirectConfig] -> ShowS # | |
| ToJSON RedirectConfig Source # | |
| Defined in Keter.Types.V10 Methods toJSON :: RedirectConfig -> Value # toEncoding :: RedirectConfig -> Encoding # toJSONList :: [RedirectConfig] -> Value # toEncodingList :: [RedirectConfig] -> Encoding # | |
| ParseYamlFile RedirectConfig Source # | |
| Defined in Keter.Types.V10 Methods parseYamlFile :: BaseDir -> Value -> Parser RedirectConfig Source # | |
| ToCurrent RedirectConfig Source # | |
| Defined in Keter.Types.V10 Associated Types type Previous RedirectConfig Source # Methods toCurrent :: Previous RedirectConfig -> RedirectConfig Source # | |
| type Previous RedirectConfig Source # | |
| Defined in Keter.Types.V10 | |
data RedirectAction Source #
Constructors
| RedirectAction !SourcePath !RedirectDest | 
Instances
| Show RedirectAction Source # | |
| Defined in Keter.Types.V10 Methods showsPrec :: Int -> RedirectAction -> ShowS # show :: RedirectAction -> String # showList :: [RedirectAction] -> ShowS # | |
| ToJSON RedirectAction Source # | |
| Defined in Keter.Types.V10 Methods toJSON :: RedirectAction -> Value # toEncoding :: RedirectAction -> Encoding # toJSONList :: [RedirectAction] -> Value # toEncodingList :: [RedirectAction] -> Encoding # | |
| FromJSON RedirectAction Source # | |
| Defined in Keter.Types.V10 Methods parseJSON :: Value -> Parser RedirectAction # parseJSONList :: Value -> Parser [RedirectAction] # | |
data SourcePath Source #
Constructors
| SPAny | |
| SPSpecific !Text | 
Instances
| Show SourcePath Source # | |
| Defined in Keter.Types.V10 Methods showsPrec :: Int -> SourcePath -> ShowS # show :: SourcePath -> String # showList :: [SourcePath] -> ShowS # | |
data RedirectDest Source #
Instances
| Show RedirectDest Source # | |
| Defined in Keter.Types.V10 Methods showsPrec :: Int -> RedirectDest -> ShowS # show :: RedirectDest -> String # showList :: [RedirectDest] -> ShowS # | |
| ToJSON RedirectDest Source # | |
| Defined in Keter.Types.V10 Methods toJSON :: RedirectDest -> Value # toEncoding :: RedirectDest -> Encoding # toJSONList :: [RedirectDest] -> Value # toEncodingList :: [RedirectDest] -> Encoding # | |
| FromJSON RedirectDest Source # | |
| Defined in Keter.Types.V10 | |
data WebAppConfig port Source #
Constructors
| WebAppConfig | |
| Fields 
 | |
Instances
| Show port => Show (WebAppConfig port) Source # | |
| Defined in Keter.Types.V10 Methods showsPrec :: Int -> WebAppConfig port -> ShowS # show :: WebAppConfig port -> String # showList :: [WebAppConfig port] -> ShowS # | |
| ToJSON (WebAppConfig ()) Source # | |
| Defined in Keter.Types.V10 Methods toJSON :: WebAppConfig () -> Value # toEncoding :: WebAppConfig () -> Encoding # toJSONList :: [WebAppConfig ()] -> Value # toEncodingList :: [WebAppConfig ()] -> Encoding # | |
| ParseYamlFile (WebAppConfig ()) Source # | |
| Defined in Keter.Types.V10 Methods parseYamlFile :: BaseDir -> Value -> Parser (WebAppConfig ()) Source # | |
| ToCurrent (WebAppConfig ()) Source # | |
| Defined in Keter.Types.V10 Associated Types type Previous (WebAppConfig ()) Source # Methods toCurrent :: Previous (WebAppConfig ()) -> WebAppConfig () Source # | |
| type Previous (WebAppConfig ()) Source # | |
| Defined in Keter.Types.V10 | |
Constructors
| AIBundle !FilePath !EpochTime | |
| AIData !BundleConfig | 
data BackgroundConfig Source #
Constructors
| BackgroundConfig | |
| Fields 
 | |
Instances
| Show BackgroundConfig Source # | |
| Defined in Keter.Types.V10 Methods showsPrec :: Int -> BackgroundConfig -> ShowS # show :: BackgroundConfig -> String # showList :: [BackgroundConfig] -> ShowS # | |
| ToJSON BackgroundConfig Source # | |
| Defined in Keter.Types.V10 Methods toJSON :: BackgroundConfig -> Value # toEncoding :: BackgroundConfig -> Encoding # toJSONList :: [BackgroundConfig] -> Value # toEncodingList :: [BackgroundConfig] -> Encoding # | |
| ParseYamlFile BackgroundConfig Source # | |
| Defined in Keter.Types.V10 Methods parseYamlFile :: BaseDir -> Value -> Parser BackgroundConfig Source # | |
data RestartCount Source #
Constructors
| UnlimitedRestarts | |
| LimitedRestarts !Word | 
Instances
| Show RestartCount Source # | |
| Defined in Keter.Types.V10 Methods showsPrec :: Int -> RestartCount -> ShowS # show :: RestartCount -> String # showList :: [RestartCount] -> ShowS # | |
| FromJSON RestartCount Source # | |
| Defined in Keter.Types.V10 | |