Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Moonshine a
- data LoggingConfig = LoggingConfig {}
- runMoonshine :: Moonshine a -> IO a
- route :: [(ByteString, Moonshine ())] -> Moonshine ()
- makeTimer :: Text -> Moonshine Timer
- timerAdd :: (Real time, MonadIO io) => Timer -> time -> io ()
- data Timer
- getUserConfig :: (MonadIO io, FromJSON config) => io config
- timed :: Text -> Moonshine a -> Moonshine a
- liftSnap :: Snap () -> Moonshine ()
- liftIO :: MonadIO m => forall a. IO a -> m a
- badRequest :: String -> Snap a
- requiredParam :: ByteString -> Snap ByteString
- requiredUtf8Param :: ByteString -> Snap Text
- writeJSON :: ToJSON json => json -> Snap ()
- setBanner :: String -> IO ()
- readJSON :: FromJSON json => Int64 -> Snap json
- created :: Snap ()
- noContent :: Snap ()
- methodNotAllowed :: [Method] -> Snap a
- assertMethod :: Method -> Snap a -> Snap a
- timedIO :: MonadIO io => Timer -> io a -> io a
- makeGauge :: Text -> Moonshine Gauge
- gaugeInc :: MonadIO io => Gauge -> io ()
- gaugeDec :: MonadIO io => Gauge -> io ()
- gaugeSet :: MonadIO io => Gauge -> Int64 -> io ()
- gaugeAdd :: MonadIO io => Gauge -> Int64 -> io ()
- gaugeSubtract :: MonadIO io => Gauge -> Int64 -> io ()
- data Gauge
- notFound :: Snap a
- setServerVersion :: String -> Version -> Moonshine ()
- class ResponseEntity e where
- getContentType :: e -> ContentType
- getBytes :: e -> ByteString
- writeEntity :: ResponseEntity e => e -> Snap ()
- getMethod :: Snap Method
- conflict :: Snap ()
- type ContentType = ByteString
- class RequestEntity e where
- decodeEntity :: Maybe ContentType -> ByteString -> DecodeResult e
- data DecodeResult e
- = Unsupported
- | BadEntity String
- | Ok e
- readEntity :: RequestEntity e => Int64 -> Snap e
- unsupportedMediaType :: Snap a
- exactPath :: Snap a -> Snap a
Documentation
The moonshine monad.
data LoggingConfig Source
Logging configuration that Moonshine should use to initialize logging.
This type is an instance of FromJSON, so you can easily use it in your configuration as:
data MyConfig = MyConfig { logging :: LoggingConfig } deriving (Generic) instance FromJSON MyConfig
runMoonshine :: Moonshine a -> IO a Source
Execute an insance of the Moonshine monad. This starts up a server and never returns.
route :: [(ByteString, Moonshine ())] -> Moonshine () Source
Like route
, but that automatically sets up metrics for the
specified routes.
getUserConfig :: (MonadIO io, FromJSON config) => io config Source
Returns the user config.
Wrap a Moonshine
in a timer, so that timing data for invocations
will be logged to the metrics handler.
badRequest :: String -> Snap a Source
Using this will short-circuit the snap monad (in much the same way as
fail
does for all monads), but instead the regular meaning of "fail"
in the snap monad (which allows the framework to choose some other
path), this short-circuit causes a 400 Bad Request to be returned no
matter what.
requiredParam :: ByteString -> Snap ByteString Source
Look up a parameter, and if it doesn't exist, then cause a 400 BadRequest to be returned to the user
requiredUtf8Param :: ByteString -> Snap Text Source
Look up a parameter, and decode it using utf8. If the parameter doesn't exist, then cause a 400 BadReqeust to be returned to the user.
writeJSON :: ToJSON json => json -> Snap () Source
Write a ToJSON
instance to the entity body, setting the Content-Type
header to application/json
.
readJSON :: FromJSON json => Int64 -> Snap json Source
Read a FromJSON
from the request entity, causing a 400 bad request on
a parsing error. The first argument specifies the maximum size we are
willing to read. This method delegates to readRequestBody
,
so an exception will be thrown in the case where the maximum size
is exceeded.
methodNotAllowed :: [Method] -> Snap a Source
Short circuit with a 405 Method Not Allowed. Also, set the Allow header with the allowed methods.
assertMethod :: Method -> Snap a -> Snap a Source
Asserts that the request was made using a particular HTTP request method. If the assertion fails, then the request will result in a 405 Method Not Allowed.
timedIO :: MonadIO io => Timer -> io a -> io a Source
Time how long it takes to perform some kind of IO. This function is
compatible with any MonadIO
.
gaugeSet :: MonadIO io => Gauge -> Int64 -> io () Source
Set the gauge the a specific value one from a gauge value.
gaugeSubtract :: MonadIO io => Gauge -> Int64 -> io () Source
Subtrace a value from a gauge.
:: String |
|
-> Version |
|
-> Moonshine () |
Utility method that sets the Server:
header to something sensible.
class ResponseEntity e where Source
The class of things that can be used as http response entities.
getContentType :: e -> ContentType Source
The content type of the respone entity.
getBytes :: e -> ByteString Source
The bytes associated with the response entity.
writeEntity :: ResponseEntity e => e -> Snap () Source
A more powerful version of writeJSON. This function writes generic
ResponseEntity
s, and sets the right content type for them.
type ContentType = ByteString Source
ContentType is an alias for ByteString
class RequestEntity e where Source
The class of things that can be read as request entitys.
decodeEntity :: Maybe ContentType -> ByteString -> DecodeResult e Source
Decode the entity, according to the specified content type.
data DecodeResult e Source
The result of trying to decode a request entity.
Unsupported | Signifies an unsupported content type. |
BadEntity String | Signifies that the request entity is invalid, and provides some kind of reason why. |
Ok e | Successfully decoded the entity. |
readEntity :: RequestEntity e => Int64 -> Snap e Source
Reads and decodes a request entity, returning the appropriate error
responses if the entity can't be decoded: 415 Unsupported Media Type
if the
content type is not supported, or 400 Bad Request
if the content type is
supported, but the entity can't be decoded.
unsupportedMediaType :: Snap a Source
Short circuit with a 415 response.