Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
data RequestData a Source #
BodyRequestData (ByteString -> Either Text a) | |
PureRequestData a |
Instances
Functor RequestData Source # | |
Defined in Web.Eved.Server fmap :: (a -> b) -> RequestData a -> RequestData b # (<$) :: a -> RequestData b -> RequestData a # |
newtype EvedServerT m a Source #
EvedServerT | |
|
Instances
EvedAuth (EvedServerT m) Source # | |
Defined in Web.Eved.Auth auth_ :: NonEmpty (AuthScheme a) -> EvedServerT m b -> EvedServerT m (a -> b) Source # | |
Eved (EvedServerT m) m Source # | |
Defined in Web.Eved.Server (.<|>) :: EvedServerT m a -> EvedServerT m b -> EvedServerT m (a :<|> b) Source # lit :: Text -> EvedServerT m a -> EvedServerT m a Source # capture :: Text -> UrlElement a -> EvedServerT m b -> EvedServerT m (a -> b) Source # reqBody :: NonEmpty (ContentType a) -> EvedServerT m b -> EvedServerT m (a -> b) Source # queryParam :: Text -> QueryParam a -> EvedServerT m b -> EvedServerT m (a -> b) Source # verb :: StdMethod -> Status -> NonEmpty (ContentType a) -> EvedServerT m (m a) Source # |
server :: (forall a. m a -> IO a) -> a -> EvedServerT m a -> Application Source #
data RoutingError Source #
PathError | |
CaptureError Text | |
QueryParamParseError Text | |
NoContentMatchError | |
NoAcceptMatchError | |
NoMethodMatchError |
Instances
Eq RoutingError Source # | |
Defined in Web.Eved.Server (==) :: RoutingError -> RoutingError -> Bool # (/=) :: RoutingError -> RoutingError -> Bool # | |
Ord RoutingError Source # | |
Defined in Web.Eved.Server compare :: RoutingError -> RoutingError -> Ordering # (<) :: RoutingError -> RoutingError -> Bool # (<=) :: RoutingError -> RoutingError -> Bool # (>) :: RoutingError -> RoutingError -> Bool # (>=) :: RoutingError -> RoutingError -> Bool # max :: RoutingError -> RoutingError -> RoutingError # min :: RoutingError -> RoutingError -> RoutingError # | |
Show RoutingError Source # | |
Defined in Web.Eved.Server showsPrec :: Int -> RoutingError -> ShowS # show :: RoutingError -> String # showList :: [RoutingError] -> ShowS # | |
Exception RoutingError Source # | |
Defined in Web.Eved.Server |
newtype UserApplicationError a Source #
Instances
Show a => Show (UserApplicationError a) Source # | |
Defined in Web.Eved.Server showsPrec :: Int -> UserApplicationError a -> ShowS # show :: UserApplicationError a -> String # showList :: [UserApplicationError a] -> ShowS # | |
Exception a => Exception (UserApplicationError a) Source # | |
Defined in Web.Eved.Server toException :: UserApplicationError a -> SomeException # fromException :: SomeException -> Maybe (UserApplicationError a) # displayException :: UserApplicationError a -> String # |
data ServerError Source #
ServerError | |
|
Instances
Show ServerError Source # | |
Defined in Web.Eved.Server showsPrec :: Int -> ServerError -> ShowS # show :: ServerError -> String # showList :: [ServerError] -> ShowS # | |
Exception ServerError Source # | |
Defined in Web.Eved.Server |