Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- data ByteString
- data Text
- data Map k a
- type FilePath = String
- class (Typeable e, Show e) => Exception e
- data SomeException
- data Set a
- data SSLConfig
- data AppId
- data KeterException
- = CannotParsePostgres FilePath
- | ExitCodeFailure FilePath ExitCode
- | NoPortsAvailable
- | InvalidConfigFile ParseException
- | InvalidKeterConfigFile !FilePath !ParseException
- | CannotReserveHosts !AppId !(Map Host AppId)
- | FileNotExecutable !FilePath
- | ExecutableNotFound !FilePath
- | EnsureAliveShouldBeBiggerThenZero {
- keterExceptionGot :: !Int
- data LogMessage
- = ProcessCreated FilePath
- | InvalidBundle FilePath SomeException
- | ProcessDidNotStart FilePath
- | ExceptionThrown Text SomeException
- | RemovingPort Int
- | UnpackingBundle FilePath
- | TerminatingApp Text
- | FinishedReloading Text
- | TerminatingOldProcess AppId
- | RemovingOldFolder FilePath
- | ReceivedInotifyEvent Text
- | ProcessWaiting FilePath
- | OtherMessage Text
- | ErrorStartingBundle Text SomeException
- | SanityChecksPassed
- | ReservingHosts AppId (Set Host)
- | ForgetingReservations AppId (Set Host)
- | ActivatingApp AppId (Set Host)
- | DeactivatingApp AppId (Set Host)
- | ReactivatingApp AppId (Set Host) (Set Host)
- | WatchedFile Text FilePath
- | ReloadFrom (Maybe String) String
- | Terminating String
- | LaunchInitial
- | LaunchCli
- | StartWatching
- | StartListening
- | BindCli AddrInfo
- | ReceivedCliConnection SockAddr
- | KillingApp Port Text
- type HostBS = CI ByteString
- type Host = CI Text
- type Port = Int
- class ToCurrent a where
- type Plugins = [Plugin]
- data Plugin = Plugin {}
- type Appname = Text
- getAppname :: FilePath -> Text
- logEx :: Q Exp
- data RewriteRule = RewriteRule {
- ruleHeader :: Text
- ruleRegex :: Text
- ruleReplacement :: Text
- data ReverseProxyConfig = ReverseProxyConfig {}
- data PortSettings = PortSettings {}
- data TLSConfig = TLSConfig !Settings !FilePath !FilePath (Maybe Config)
- data RestartCount
- data BackgroundConfig = BackgroundConfig {
- bgconfigExec :: !FilePath
- bgconfigArgs :: !(Vector Text)
- bgconfigEnvironment :: !(Map Text Text)
- bgconfigRestartCount :: !RestartCount
- bgconfigRestartDelaySeconds :: !Word
- bgconfigForwardEnv :: !(Set Text)
- data AppInput
- 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 RedirectDest
- data SourcePath
- = SPAny
- | SPSpecific !Text
- data RedirectAction = RedirectAction !SourcePath !RedirectDest
- 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
- type ProxyAction = (ProxyActionRaw, RequiresSecure)
- data ProxyActionRaw
- data StanzaRaw port
- data Stanza port = Stanza (StanzaRaw port) RequiresSecure
- type RequiresSecure = Bool
- 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)
- data ListeningPort
- = LPSecure !HostPreference !Port !FilePath !(Vector FilePath) !FilePath !Bool
- | LPInsecure !HostPreference !Port
- data BundleConfig = BundleConfig {
- bconfigStanzas :: !(Vector (Stanza ()))
- bconfigPlugins :: !Object
Documentation
data ByteString #
A space-efficient representation of a Word8
vector, supporting many
efficient operations.
A ByteString
contains 8-bit bytes, or by using the operations from
Data.ByteString.Char8 it can be interpreted as containing 8-bit
characters.
Instances
A space efficient, packed, unboxed Unicode text type.
Instances
A Map from keys k
to values a
.
The Semigroup
operation for Map
is union
, which prefers
values from the left operand. If m1
maps a key k
to a value
a1
, and m2
maps the same key to a different value a2
, then
their union m1 <> m2
maps k
to a1
.
Instances
Eq2 Map | Since: containers-0.5.9 |
Ord2 Map | Since: containers-0.5.9 |
Defined in Data.Map.Internal | |
Show2 Map | Since: containers-0.5.9 |
Hashable2 Map | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
FunctorWithIndex k (Map k) | |
FoldableWithIndex k (Map k) | |
TraversableWithIndex k (Map k) | |
Functor (Map k) | |
Foldable (Map k) | Folds in order of increasing key. |
Defined in Data.Map.Internal fold :: Monoid m => Map k m -> m # foldMap :: Monoid m => (a -> m) -> Map k a -> m # foldMap' :: Monoid m => (a -> m) -> Map k a -> m # foldr :: (a -> b -> b) -> b -> Map k a -> b # foldr' :: (a -> b -> b) -> b -> Map k a -> b # foldl :: (b -> a -> b) -> b -> Map k a -> b # foldl' :: (b -> a -> b) -> b -> Map k a -> b # foldr1 :: (a -> a -> a) -> Map k a -> a # foldl1 :: (a -> a -> a) -> Map k a -> a # elem :: Eq a => a -> Map k a -> Bool # maximum :: Ord a => Map k a -> a # minimum :: Ord a => Map k a -> a # | |
Traversable (Map k) | Traverses in order of increasing key. |
ToJSONKey k => ToJSON1 (Map k) | |
Defined in Data.Aeson.Types.ToJSON liftToJSON :: (a -> Value) -> ([a] -> Value) -> Map k a -> Value # liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Map k a] -> Value # liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Map k a -> Encoding # liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Map k a] -> Encoding # | |
(FromJSONKey k, Ord k) => FromJSON1 (Map k) | |
Eq k => Eq1 (Map k) | Since: containers-0.5.9 |
Ord k => Ord1 (Map k) | Since: containers-0.5.9 |
Defined in Data.Map.Internal | |
(Ord k, Read k) => Read1 (Map k) | Since: containers-0.5.9 |
Defined in Data.Map.Internal | |
Show k => Show1 (Map k) | Since: containers-0.5.9 |
Hashable k => Hashable1 (Map k) | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
Ord k => IsList (Map k v) | Since: containers-0.5.6.2 |
(Eq k, Eq a) => Eq (Map k a) | |
(Data k, Data a, Ord k) => Data (Map k a) | |
Defined in Data.Map.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Map k a -> c (Map k a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Map k a) # toConstr :: Map k a -> Constr # dataTypeOf :: Map k a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Map k a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Map k a)) # gmapT :: (forall b. Data b => b -> b) -> Map k a -> Map k a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Map k a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Map k a -> r # gmapQ :: (forall d. Data d => d -> u) -> Map k a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Map k a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) # | |
(Ord k, Ord v) => Ord (Map k v) | |
(Ord k, Read k, Read e) => Read (Map k e) | |
(Show k, Show a) => Show (Map k a) | |
Ord k => Semigroup (Map k v) | |
Ord k => Monoid (Map k v) | |
(Hashable k, Hashable v) => Hashable (Map k v) | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
(ToJSON v, ToJSONKey k) => ToJSON (Map k v) | |
Defined in Data.Aeson.Types.ToJSON | |
(FromJSONKey k, Ord k, FromJSON v) => FromJSON (Map k v) | |
(NFData k, NFData a) => NFData (Map k a) | |
Defined in Data.Map.Internal | |
MonoFunctor (Map k v) | |
MonoFoldable (Map k v) | |
Defined in Data.MonoTraversable ofoldMap :: Monoid m => (Element (Map k v) -> m) -> Map k v -> m # ofoldr :: (Element (Map k v) -> b -> b) -> b -> Map k v -> b # ofoldl' :: (a -> Element (Map k v) -> a) -> a -> Map k v -> a # otoList :: Map k v -> [Element (Map k v)] # oall :: (Element (Map k v) -> Bool) -> Map k v -> Bool # oany :: (Element (Map k v) -> Bool) -> Map k v -> Bool # olength64 :: Map k v -> Int64 # ocompareLength :: Integral i => Map k v -> i -> Ordering # otraverse_ :: Applicative f => (Element (Map k v) -> f b) -> Map k v -> f () # ofor_ :: Applicative f => Map k v -> (Element (Map k v) -> f b) -> f () # omapM_ :: Applicative m => (Element (Map k v) -> m ()) -> Map k v -> m () # oforM_ :: Applicative m => Map k v -> (Element (Map k v) -> m ()) -> m () # ofoldlM :: Monad m => (a -> Element (Map k v) -> m a) -> a -> Map k v -> m a # ofoldMap1Ex :: Semigroup m => (Element (Map k v) -> m) -> Map k v -> m # ofoldr1Ex :: (Element (Map k v) -> Element (Map k v) -> Element (Map k v)) -> Map k v -> Element (Map k v) # ofoldl1Ex' :: (Element (Map k v) -> Element (Map k v) -> Element (Map k v)) -> Map k v -> Element (Map k v) # headEx :: Map k v -> Element (Map k v) # lastEx :: Map k v -> Element (Map k v) # unsafeHead :: Map k v -> Element (Map k v) # unsafeLast :: Map k v -> Element (Map k v) # maximumByEx :: (Element (Map k v) -> Element (Map k v) -> Ordering) -> Map k v -> Element (Map k v) # minimumByEx :: (Element (Map k v) -> Element (Map k v) -> Ordering) -> Map k v -> Element (Map k v) # | |
MonoTraversable (Map k v) | |
Ord k => GrowingAppend (Map k v) | |
Defined in Data.MonoTraversable | |
type Item (Map k v) | |
Defined in Data.Map.Internal | |
type Element (Map k v) | |
Defined in Data.MonoTraversable |
File and directory names are values of type String
, whose precise
meaning is operating system dependent. Files can be opened, yielding a
handle which can then be used to operate on the contents of that file.
class (Typeable e, Show e) => Exception e #
Any type that you wish to throw or catch as an exception must be an
instance of the Exception
class. The simplest case is a new exception
type directly below the root:
data MyException = ThisException | ThatException deriving Show instance Exception MyException
The default method definitions in the Exception
class do what we need
in this case. You can now throw and catch ThisException
and
ThatException
as exceptions:
*Main> throw ThisException `catch` \e -> putStrLn ("Caught " ++ show (e :: MyException)) Caught ThisException
In more complicated examples, you may wish to define a whole hierarchy of exceptions:
--------------------------------------------------------------------- -- Make the root exception type for all the exceptions in a compiler data SomeCompilerException = forall e . Exception e => SomeCompilerException e instance Show SomeCompilerException where show (SomeCompilerException e) = show e instance Exception SomeCompilerException compilerExceptionToException :: Exception e => e -> SomeException compilerExceptionToException = toException . SomeCompilerException compilerExceptionFromException :: Exception e => SomeException -> Maybe e compilerExceptionFromException x = do SomeCompilerException a <- fromException x cast a --------------------------------------------------------------------- -- Make a subhierarchy for exceptions in the frontend of the compiler data SomeFrontendException = forall e . Exception e => SomeFrontendException e instance Show SomeFrontendException where show (SomeFrontendException e) = show e instance Exception SomeFrontendException where toException = compilerExceptionToException fromException = compilerExceptionFromException frontendExceptionToException :: Exception e => e -> SomeException frontendExceptionToException = toException . SomeFrontendException frontendExceptionFromException :: Exception e => SomeException -> Maybe e frontendExceptionFromException x = do SomeFrontendException a <- fromException x cast a --------------------------------------------------------------------- -- Make an exception type for a particular frontend compiler exception data MismatchedParentheses = MismatchedParentheses deriving Show instance Exception MismatchedParentheses where toException = frontendExceptionToException fromException = frontendExceptionFromException
We can now catch a MismatchedParentheses
exception as
MismatchedParentheses
, SomeFrontendException
or
SomeCompilerException
, but not other types, e.g. IOException
:
*Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses)) Caught MismatchedParentheses *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException)) Caught MismatchedParentheses *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException)) Caught MismatchedParentheses *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: IOException)) *** Exception: MismatchedParentheses
Instances
data SomeException #
The SomeException
type is the root of the exception type hierarchy.
When an exception of type e
is thrown, behind the scenes it is
encapsulated in a SomeException
.
Instances
Show SomeException | Since: base-3.0 |
Defined in GHC.Exception.Type showsPrec :: Int -> SomeException -> ShowS # show :: SomeException -> String # showList :: [SomeException] -> ShowS # | |
Exception SomeException | Since: base-3.0 |
Defined in GHC.Exception.Type |
A set of values a
.
Instances
Foldable Set | Folds in order of increasing key. |
Defined in Data.Set.Internal fold :: Monoid m => Set m -> m # foldMap :: Monoid m => (a -> m) -> Set a -> m # foldMap' :: Monoid m => (a -> m) -> Set a -> m # foldr :: (a -> b -> b) -> b -> Set a -> b # foldr' :: (a -> b -> b) -> b -> Set a -> b # foldl :: (b -> a -> b) -> b -> Set a -> b # foldl' :: (b -> a -> b) -> b -> Set a -> b # foldr1 :: (a -> a -> a) -> Set a -> a # foldl1 :: (a -> a -> a) -> Set a -> a # elem :: Eq a => a -> Set a -> Bool # maximum :: Ord a => Set a -> a # | |
ToJSON1 Set | |
Defined in Data.Aeson.Types.ToJSON | |
Eq1 Set | Since: containers-0.5.9 |
Ord1 Set | Since: containers-0.5.9 |
Defined in Data.Set.Internal | |
Show1 Set | Since: containers-0.5.9 |
Hashable1 Set | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
Ord a => IsList (Set a) | Since: containers-0.5.6.2 |
Eq a => Eq (Set a) | |
(Data a, Ord a) => Data (Set a) | |
Defined in Data.Set.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Set a -> c (Set a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Set a) # dataTypeOf :: Set a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Set a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Set a)) # gmapT :: (forall b. Data b => b -> b) -> Set a -> Set a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Set a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Set a -> r # gmapQ :: (forall d. Data d => d -> u) -> Set a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Set a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) # | |
Ord a => Ord (Set a) | |
(Read a, Ord a) => Read (Set a) | |
Show a => Show (Set a) | |
Ord a => Semigroup (Set a) | Since: containers-0.5.7 |
Ord a => Monoid (Set a) | |
Hashable v => Hashable (Set v) | Since: hashable-1.3.4.0 |
Defined in Data.Hashable.Class | |
ToJSON a => ToJSON (Set a) | |
Defined in Data.Aeson.Types.ToJSON | |
(Ord a, FromJSON a) => FromJSON (Set a) | |
NFData a => NFData (Set a) | |
Defined in Data.Set.Internal | |
Ord e => MonoFoldable (Set e) | |
Defined in Data.MonoTraversable ofoldMap :: Monoid m => (Element (Set e) -> m) -> Set e -> m # ofoldr :: (Element (Set e) -> b -> b) -> b -> Set e -> b # ofoldl' :: (a -> Element (Set e) -> a) -> a -> Set e -> a # otoList :: Set e -> [Element (Set e)] # oall :: (Element (Set e) -> Bool) -> Set e -> Bool # oany :: (Element (Set e) -> Bool) -> Set e -> Bool # ocompareLength :: Integral i => Set e -> i -> Ordering # otraverse_ :: Applicative f => (Element (Set e) -> f b) -> Set e -> f () # ofor_ :: Applicative f => Set e -> (Element (Set e) -> f b) -> f () # omapM_ :: Applicative m => (Element (Set e) -> m ()) -> Set e -> m () # oforM_ :: Applicative m => Set e -> (Element (Set e) -> m ()) -> m () # ofoldlM :: Monad m => (a -> Element (Set e) -> m a) -> a -> Set e -> m a # ofoldMap1Ex :: Semigroup m => (Element (Set e) -> m) -> Set e -> m # ofoldr1Ex :: (Element (Set e) -> Element (Set e) -> Element (Set e)) -> Set e -> Element (Set e) # ofoldl1Ex' :: (Element (Set e) -> Element (Set e) -> Element (Set e)) -> Set e -> Element (Set e) # headEx :: Set e -> Element (Set e) # lastEx :: Set e -> Element (Set e) # unsafeHead :: Set e -> Element (Set e) # unsafeLast :: Set e -> Element (Set e) # maximumByEx :: (Element (Set e) -> Element (Set e) -> Ordering) -> Set e -> Element (Set e) # minimumByEx :: (Element (Set e) -> Element (Set e) -> Ordering) -> Set e -> Element (Set e) # | |
MonoPointed (Set a) | |
Ord v => GrowingAppend (Set v) | |
Defined in Data.MonoTraversable | |
(ParseYamlFile a, Ord a) => ParseYamlFile (Set a) Source # | |
Defined in Data.Yaml.FilePath | |
type Item (Set a) | |
Defined in Data.Set.Internal | |
type Element (Set e) | |
Defined in Data.MonoTraversable |
data KeterException Source #
Instances
Show KeterException Source # | |
Defined in Keter.Types.Common showsPrec :: Int -> KeterException -> ShowS # show :: KeterException -> String # showList :: [KeterException] -> ShowS # | |
Exception KeterException Source # | |
Defined in Keter.Types.Common |
data LogMessage Source #
Instances
Show LogMessage Source # | |
Defined in Keter.Types.Common showsPrec :: Int -> LogMessage -> ShowS # show :: LogMessage -> String # showList :: [LogMessage] -> ShowS # |
type HostBS = CI ByteString Source #
class ToCurrent a where Source #
Used for versioning data types.
Instances
ToCurrent RedirectConfig Source # | |
Defined in Keter.Types.V10 type Previous RedirectConfig Source # | |
ToCurrent StaticFilesConfig Source # | |
Defined in Keter.Types.V10 type Previous StaticFilesConfig Source # | |
ToCurrent KeterConfig Source # | |
Defined in Keter.Types.V10 type Previous KeterConfig Source # | |
ToCurrent BundleConfig Source # | |
Defined in Keter.Types.V10 type Previous BundleConfig Source # | |
ToCurrent a => ToCurrent (Maybe a) Source # | |
ToCurrent (WebAppConfig ()) Source # | |
Defined in Keter.Types.V10 type Previous (WebAppConfig ()) Source # toCurrent :: Previous (WebAppConfig ()) -> WebAppConfig () Source # |
Name of the application. Should just be the basename of the application file.
getAppname :: FilePath -> Text Source #
data RewriteRule Source #
RewriteRule | |
|
Instances
data ReverseProxyConfig Source #
Instances
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.Types.V04 parseJSON :: Value -> Parser PortSettings # parseJSONList :: Value -> Parser [PortSettings] # | |
Default PortSettings Source # | |
Defined in Keter.Types.V04 def :: PortSettings # |
Instances
ParseYamlFile TLSConfig Source # | |
Defined in Keter.Types.V04 |
data RestartCount Source #
Instances
Show RestartCount Source # | |
Defined in Keter.Types.V10 showsPrec :: Int -> RestartCount -> ShowS # show :: RestartCount -> String # showList :: [RestartCount] -> ShowS # | |
FromJSON RestartCount Source # | |
Defined in Keter.Types.V10 parseJSON :: Value -> Parser RestartCount # parseJSONList :: Value -> Parser [RestartCount] # |
data BackgroundConfig Source #
BackgroundConfig | |
|
Instances
Show BackgroundConfig Source # | |
Defined in Keter.Types.V10 showsPrec :: Int -> BackgroundConfig -> ShowS # show :: BackgroundConfig -> String # showList :: [BackgroundConfig] -> ShowS # | |
ToJSON BackgroundConfig Source # | |
Defined in Keter.Types.V10 toJSON :: BackgroundConfig -> Value # toEncoding :: BackgroundConfig -> Encoding # toJSONList :: [BackgroundConfig] -> Value # toEncodingList :: [BackgroundConfig] -> Encoding # | |
ParseYamlFile BackgroundConfig Source # | |
Defined in Keter.Types.V10 parseYamlFile :: BaseDir -> Value -> Parser BackgroundConfig Source # |
data WebAppConfig port Source #
WebAppConfig | |
|
Instances
Show port => Show (WebAppConfig port) Source # | |
Defined in Keter.Types.V10 showsPrec :: Int -> WebAppConfig port -> ShowS # show :: WebAppConfig port -> String # showList :: [WebAppConfig port] -> ShowS # | |
ToJSON (WebAppConfig ()) Source # | |
Defined in Keter.Types.V10 toJSON :: WebAppConfig () -> Value # toEncoding :: WebAppConfig () -> Encoding # toJSONList :: [WebAppConfig ()] -> Value # toEncodingList :: [WebAppConfig ()] -> Encoding # | |
ParseYamlFile (WebAppConfig ()) Source # | |
Defined in Keter.Types.V10 parseYamlFile :: BaseDir -> Value -> Parser (WebAppConfig ()) Source # | |
ToCurrent (WebAppConfig ()) Source # | |
Defined in Keter.Types.V10 type Previous (WebAppConfig ()) Source # toCurrent :: Previous (WebAppConfig ()) -> WebAppConfig () Source # | |
type Previous (WebAppConfig ()) Source # | |
Defined in Keter.Types.V10 |
data RedirectDest Source #
Instances
Show RedirectDest Source # | |
Defined in Keter.Types.V10 showsPrec :: Int -> RedirectDest -> ShowS # show :: RedirectDest -> String # showList :: [RedirectDest] -> ShowS # | |
ToJSON RedirectDest Source # | |
Defined in Keter.Types.V10 toJSON :: RedirectDest -> Value # toEncoding :: RedirectDest -> Encoding # toJSONList :: [RedirectDest] -> Value # toEncodingList :: [RedirectDest] -> Encoding # | |
FromJSON RedirectDest Source # | |
Defined in Keter.Types.V10 parseJSON :: Value -> Parser RedirectDest # parseJSONList :: Value -> Parser [RedirectDest] # |
data SourcePath Source #
Instances
Show SourcePath Source # | |
Defined in Keter.Types.V10 showsPrec :: Int -> SourcePath -> ShowS # show :: SourcePath -> String # showList :: [SourcePath] -> ShowS # |
data RedirectAction Source #
Instances
Show RedirectAction Source # | |
Defined in Keter.Types.V10 showsPrec :: Int -> RedirectAction -> ShowS # show :: RedirectAction -> String # showList :: [RedirectAction] -> ShowS # | |
ToJSON RedirectAction Source # | |
Defined in Keter.Types.V10 toJSON :: RedirectAction -> Value # toEncoding :: RedirectAction -> Encoding # toJSONList :: [RedirectAction] -> Value # toEncodingList :: [RedirectAction] -> Encoding # | |
FromJSON RedirectAction Source # | |
Defined in Keter.Types.V10 parseJSON :: Value -> Parser RedirectAction # parseJSONList :: Value -> Parser [RedirectAction] # |
data RedirectConfig Source #
RedirectConfig | |
|
Instances
Show RedirectConfig Source # | |
Defined in Keter.Types.V10 showsPrec :: Int -> RedirectConfig -> ShowS # show :: RedirectConfig -> String # showList :: [RedirectConfig] -> ShowS # | |
ToJSON RedirectConfig Source # | |
Defined in Keter.Types.V10 toJSON :: RedirectConfig -> Value # toEncoding :: RedirectConfig -> Encoding # toJSONList :: [RedirectConfig] -> Value # toEncodingList :: [RedirectConfig] -> Encoding # | |
ParseYamlFile RedirectConfig Source # | |
Defined in Keter.Types.V10 parseYamlFile :: BaseDir -> Value -> Parser RedirectConfig Source # | |
ToCurrent RedirectConfig Source # | |
Defined in Keter.Types.V10 type Previous RedirectConfig Source # | |
type Previous RedirectConfig Source # | |
Defined in Keter.Types.V10 |
data StaticFilesConfig Source #
StaticFilesConfig | |
|
Instances
Show StaticFilesConfig Source # | |
Defined in Keter.Types.V10 showsPrec :: Int -> StaticFilesConfig -> ShowS # show :: StaticFilesConfig -> String # showList :: [StaticFilesConfig] -> ShowS # | |
ToJSON StaticFilesConfig Source # | |
Defined in Keter.Types.V10 toJSON :: StaticFilesConfig -> Value # toEncoding :: StaticFilesConfig -> Encoding # toJSONList :: [StaticFilesConfig] -> Value # toEncodingList :: [StaticFilesConfig] -> Encoding # | |
ParseYamlFile StaticFilesConfig Source # | |
Defined in Keter.Types.V10 parseYamlFile :: BaseDir -> Value -> Parser StaticFilesConfig Source # | |
ToCurrent StaticFilesConfig Source # | |
Defined in Keter.Types.V10 type Previous StaticFilesConfig Source # | |
type Previous StaticFilesConfig Source # | |
Defined in Keter.Types.V10 |
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.Types.V10 showsPrec :: Int -> ProxyActionRaw -> ShowS # show :: ProxyActionRaw -> String # showList :: [ProxyActionRaw] -> ShowS # |
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 |
type RequiresSecure = Bool Source #
Whether we should force redirect to HTTPS routes.
data KeterConfig Source #
KeterConfig | |
|
Instances
Default KeterConfig Source # | |
Defined in Keter.Types.V10 def :: KeterConfig # | |
ParseYamlFile KeterConfig Source # | |
Defined in Keter.Types.V10 parseYamlFile :: BaseDir -> Value -> Parser KeterConfig Source # | |
ToCurrent KeterConfig Source # | |
Defined in Keter.Types.V10 type Previous KeterConfig Source # | |
type Previous KeterConfig Source # | |
Defined in Keter.Types.V10 |
data ListeningPort Source #
LPSecure !HostPreference !Port !FilePath !(Vector FilePath) !FilePath !Bool | |
LPInsecure !HostPreference !Port |
Instances
ParseYamlFile ListeningPort Source # | |
Defined in Keter.Types.V10 parseYamlFile :: BaseDir -> Value -> Parser ListeningPort Source # |
data BundleConfig Source #
BundleConfig | |
|
Instances
Show BundleConfig Source # | |
Defined in Keter.Types.V10 showsPrec :: Int -> BundleConfig -> ShowS # show :: BundleConfig -> String # showList :: [BundleConfig] -> ShowS # | |
ToJSON BundleConfig Source # | |
Defined in Keter.Types.V10 toJSON :: BundleConfig -> Value # toEncoding :: BundleConfig -> Encoding # toJSONList :: [BundleConfig] -> Value # toEncodingList :: [BundleConfig] -> Encoding # | |
ParseYamlFile BundleConfig Source # | |
Defined in Keter.Types.V10 parseYamlFile :: BaseDir -> Value -> Parser BundleConfig Source # | |
ToCurrent BundleConfig Source # | |
Defined in Keter.Types.V10 type Previous BundleConfig Source # | |
type Previous BundleConfig Source # | |
Defined in Keter.Types.V10 |