Safe Haskell | None |
---|---|
Language | Haskell2010 |
Network.GRPC.Server.Run
Description
Convenience functions for running a HTTP2 server
Intended for unqualified import.
Synopsis
- data ServerConfig = ServerConfig {}
- data InsecureConfig
- = InsecureConfig { }
- | InsecureUnix { }
- data SecureConfig = SecureConfig {}
- runServer :: HTTP2Settings -> ServerConfig -> Server -> IO ()
- runServerWithHandlers :: ServerParams -> ServerConfig -> [SomeRpcHandler IO] -> IO ()
- data RunningServer
- forkServer :: HTTP2Settings -> ServerConfig -> Server -> (RunningServer -> IO a) -> IO a
- waitServer :: RunningServer -> IO ()
- waitServerSTM :: RunningServer -> STM (Either SomeException (), Either SomeException ())
- getInsecureSocket :: RunningServer -> STM Socket
- getSecureSocket :: RunningServer -> STM Socket
- getServerSocket :: RunningServer -> STM Socket
- getServerPort :: RunningServer -> IO PortNumber
- data ServerTerminated = ServerTerminated
- data CouldNotLoadCredentials = CouldNotLoadCredentials String
Configuration
data ServerConfig Source #
Server configuration
Describes the configuration of both an insecure server and a secure server.
See the documentation of runServer
for a description of what servers will
result from various configurations.
Constructors
ServerConfig | |
Fields
|
Instances
data InsecureConfig Source #
Offer insecure connection (no TLS)
Constructors
InsecureConfig | Insecure TCP connection |
Fields
| |
InsecureUnix | Insecure (but local) Unix domain socket connection |
Fields
|
Instances
Generic InsecureConfig Source # | |||||
Defined in Network.GRPC.Server.Run Associated Types
Methods from :: InsecureConfig -> Rep InsecureConfig x # to :: Rep InsecureConfig x -> InsecureConfig # | |||||
Show InsecureConfig Source # | |||||
Defined in Network.GRPC.Server.Run Methods showsPrec :: Int -> InsecureConfig -> ShowS # show :: InsecureConfig -> String # showList :: [InsecureConfig] -> ShowS # | |||||
type Rep InsecureConfig Source # | |||||
Defined in Network.GRPC.Server.Run type Rep InsecureConfig = D1 ('MetaData "InsecureConfig" "Network.GRPC.Server.Run" "grapesy-1.0.1-inplace" 'False) (C1 ('MetaCons "InsecureConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "insecureHost") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe HostName)) :*: S1 ('MetaSel ('Just "insecurePort") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PortNumber)) :+: C1 ('MetaCons "InsecureUnix" 'PrefixI 'True) (S1 ('MetaSel ('Just "insecurePath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath))) |
data SecureConfig Source #
Offer secure connection (over TLS)
Constructors
SecureConfig | |
Fields
|
Instances
Generic SecureConfig Source # | |||||
Defined in Network.GRPC.Server.Run Associated Types
| |||||
Show SecureConfig Source # | |||||
Defined in Network.GRPC.Server.Run Methods showsPrec :: Int -> SecureConfig -> ShowS # show :: SecureConfig -> String # showList :: [SecureConfig] -> ShowS # | |||||
type Rep SecureConfig Source # | |||||
Defined in Network.GRPC.Server.Run type Rep SecureConfig = D1 ('MetaData "SecureConfig" "Network.GRPC.Server.Run" "grapesy-1.0.1-inplace" 'False) (C1 ('MetaCons "SecureConfig" 'PrefixI 'True) ((S1 ('MetaSel ('Just "secureHost") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HostName) :*: (S1 ('MetaSel ('Just "securePort") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PortNumber) :*: S1 ('MetaSel ('Just "securePubCert") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath))) :*: (S1 ('MetaSel ('Just "secureChainCerts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: (S1 ('MetaSel ('Just "securePrivKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: S1 ('MetaSel ('Just "secureSslKeyLog") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SslKeyLog))))) |
Simple interface
runServer :: HTTP2Settings -> ServerConfig -> Server -> IO () Source #
Run a Server
with the given ServerConfig
.
If both configurations are disabled, runServer
will simply immediately
return. If both configurations are enabled, then two servers will be run
concurrently; one with the insecure configuration and the other with the
secure configuration. Obviously, if only one of the configurations is
enabled, then just that server will be run.
See also runServerWithHandlers
, which handles the creation of the
Server
for you.
runServerWithHandlers :: ServerParams -> ServerConfig -> [SomeRpcHandler IO] -> IO () Source #
Convenience function that combines runServer
with mkGrpcServer
NOTE: If you want to override the HTTP2Settings
, use runServer
instead.
Full interface
data RunningServer Source #
forkServer :: HTTP2Settings -> ServerConfig -> Server -> (RunningServer -> IO a) -> IO a Source #
Start the server
waitServer :: RunningServer -> IO () Source #
IO version of waitServerSTM
that rethrows exceptions
waitServerSTM :: RunningServer -> STM (Either SomeException (), Either SomeException ()) Source #
Wait for the server to terminate
Returns the results of the insecure and secure servers separately. Note that under normal circumstances the server never terminates.
getInsecureSocket :: RunningServer -> STM Socket Source #
Get the socket used by the insecure server
The socket is created as the server initializes; this function will block until that is complete. However:
- If the server throws an exception, that exception is rethrown here.
- If the server has already terminated, we throw
ServerTerminated
- If the insecure server was not enabled, it is considered to have terminated
immediately and the same
ServerTerminated
exception is thrown.
getSecureSocket :: RunningServer -> STM Socket Source #
Get the socket used by the secure server
Similar remarks apply as for getInsecureSocket
.
getServerSocket :: RunningServer -> STM Socket Source #
Get "the" socket associated with the server
Precondition: only one server must be enabled (secure or insecure).
getServerPort :: RunningServer -> IO PortNumber Source #
Get "the" port number used by the server
Precondition: only one server must be enabled (secure or insecure).
Exceptions
data ServerTerminated Source #
Constructors
ServerTerminated |
Instances
Exception ServerTerminated Source # | |
Defined in Network.GRPC.Server.Run Methods toException :: ServerTerminated -> SomeException # fromException :: SomeException -> Maybe ServerTerminated # | |
Show ServerTerminated Source # | |
Defined in Network.GRPC.Server.Run Methods showsPrec :: Int -> ServerTerminated -> ShowS # show :: ServerTerminated -> String # showList :: [ServerTerminated] -> ShowS # |
data CouldNotLoadCredentials Source #
Constructors
CouldNotLoadCredentials String | Failed to load server credentials |
Instances
Exception CouldNotLoadCredentials Source # | |
Defined in Network.GRPC.Server.Run | |
Show CouldNotLoadCredentials Source # | |
Defined in Network.GRPC.Server.Run Methods showsPrec :: Int -> CouldNotLoadCredentials -> ShowS # show :: CouldNotLoadCredentials -> String # showList :: [CouldNotLoadCredentials] -> ShowS # |