Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- data Server (a :: Type -> Type) b where
- runServerWai :: forall (es :: [Effect]) a. IOE :> es => (ByteString -> ByteString) -> Request -> (Response -> IO ResponseReceived) -> Eff (Server ': es) a -> Eff es (Maybe ResponseReceived)
- renderCookie :: [Segment] -> Cookie -> ByteString
- cookiesFromHeader :: [(ByteString, ByteString)] -> Cookies
- runServerSockets :: forall (es :: [Effect]). IOE :> es => Connection -> Request -> Eff (Server ': es) Response -> Eff es Response
- errNotHandled :: Event Text Text -> String
- data Client = Client {}
- data SocketError = InvalidMessage Text
- data ContentType
- contentType :: ContentType -> (HeaderName, ByteString)
- newtype Metadata = Metadata [(ByteString, Text)]
- newtype Host = Host {
- text :: ByteString
- data Request = Request {}
- data Response
- = Response TargetViewId (View () ())
- | NotFound
- | Redirect Url
- | Err ResponseError
- | Empty
- data ResponseError
- newtype TargetViewId = TargetViewId Text
- data Event id act = Event {}
Documentation
data Server (a :: Type -> Type) b where Source #
Low level effect mapping request/response to either HTTP or WebSockets
LoadRequest :: forall (a :: Type -> Type). Server a Request | |
SendResponse :: forall (a :: Type -> Type). Client -> Response -> Server a () |
Instances
type DispatchOf Server Source # | |
Defined in Web.Hyperbole.Effect.Server |
runServerWai :: forall (es :: [Effect]) a. IOE :> es => (ByteString -> ByteString) -> Request -> (Response -> IO ResponseReceived) -> Eff (Server ': es) a -> Eff es (Maybe ResponseReceived) Source #
renderCookie :: [Segment] -> Cookie -> ByteString Source #
cookiesFromHeader :: [(ByteString, ByteString)] -> Cookies Source #
runServerSockets :: forall (es :: [Effect]). IOE :> es => Connection -> Request -> Eff (Server ': es) Response -> Eff es Response Source #
data SocketError Source #
Instances
Show SocketError Source # | |
Defined in Web.Hyperbole.Effect.Server showsPrec :: Int -> SocketError -> ShowS # show :: SocketError -> String # showList :: [SocketError] -> ShowS # | |
Eq SocketError Source # | |
Defined in Web.Hyperbole.Effect.Server (==) :: SocketError -> SocketError -> Bool # (/=) :: SocketError -> SocketError -> Bool # |
contentType :: ContentType -> (HeaderName, ByteString) Source #
Host | |
|
Valid responses for a Hyperbole
effect. Use notFound
, etc instead.
Response TargetViewId (View () ()) | |
NotFound | |
Redirect Url | |
Err ResponseError | |
Empty |
data ResponseError Source #
ErrParse Text | |
ErrQuery Text | |
ErrSession Param Text | |
ErrOther Text | |
ErrNotHandled (Event Text Text) | |
ErrAuth |
Instances
Show ResponseError Source # | |
Defined in Web.Hyperbole.Effect.Server showsPrec :: Int -> ResponseError -> ShowS # show :: ResponseError -> String # showList :: [ResponseError] -> ShowS # |
An action, with its corresponding id