gingersnap-0.2.1.1: snap-core + aeson + postgresql-simple = delicious

Safe HaskellNone
LanguageHaskell2010

Gingersnap.Core

Contents

Synopsis

Rsp

data Rsp Source #

How we construct responses. You probably don't want to be constructing or inspecting them by hand; instead you can use rspGood, rspBadRollback, etc.

Instances
Show Rsp Source # 
Instance details

Defined in Gingersnap.Core

Methods

showsPrec :: Int -> Rsp -> ShowS #

show :: Rsp -> String #

showList :: [Rsp] -> ShowS #

rspGood :: ToJSON x => x -> Rsp Source #

This means everything's succeeded. We should commit DB changes and return a success object

rspBad :: ApiErr ae => ae -> Rsp Source #

We should send back an error object and roll back DB changes

rspBadCommit :: ApiErr ae => ae -> Rsp Source #

Like rspBad but should still commit DB changes

rspBadRollback :: ApiErr ae => ae -> Rsp Source #

The same as rspBad but more explicit that we roll back

rspGoodLBS :: ByteString -> ByteString -> Rsp Source #

First Bytestring is the content type, e.g. "application/json" Here's a helpful list: https://developer.mozilla.org/en-US/docs/Web/HTTP/Basics_of_HTTP/MIME_types/Complete_list_of_MIME_types

rspEmptyGood :: Rsp Source #

Everything worked and we send a 200, but we don't have any data to send

pureRsp

pureRsp :: IsCtx ctx => ctx -> Rsp -> Snap () Source #

Sometimes you don't need a DB connection at all!

DB Transactions

inTransaction :: IsCtx ctx => ctx -> (Connection -> IO Rsp) -> Snap () Source #

  • If you hit the DB, use this function!*

This is a lot like withTransaction, but it allows us to rollback if we want, without throwing an error. (Don't use withTransaction!)

NOTE this is for IO actions, not Snap actions. This is to ensure we can't call e.g. finishEarly and never hit the 'end transaction' code! (It also has the side benefit of keeping code fairly framework-agnostic)

inTransactionMode :: IsCtx ctx => ctx -> IsolationLevel -> ReadWriteMode -> (Connection -> IO Rsp) -> Snap () Source #

The most general version of inTransaction.

An endpoint that uses ReadOnly will keep responding even when the server is in read-only mode.

inTransaction_readOnly :: IsCtx ctx => ctx -> (Connection -> IO Rsp) -> Snap () Source #

Creates a read-only transaction and will keep responding even if the server's in read-only mode.

Note that you the programmer are asserting the DB queries are read-only. There's nothing in this library or in postgresql-simple which statically checks that to be true!

inTransaction_override :: IsCtx ctx => ctx -> (Connection -> IO Rsp) -> Snap () Source #

YOU SHOULD ONLY USE THIS ONCE

This lets you do a write transaction during read-only mode (not a read-only transaction! A time where ctxGetReadOnlyMode would return True)

You may need this so that an admin user can take the app out of read-only mode

IsCtx

class ApiErr (CtxErrType ctx) => IsCtx ctx where Source #

Don't be daunted! The only thing you need to provide (i.e. that doesn't have a default value) is ctxConnectionPool

Minimal complete definition

ctxConnectionPool

Associated Types

type CtxErrType ctx Source #

JSON requests

reqObject :: IsCtx ctx => ctx -> Snap (ReqObject ctx) Source #

reqObject' :: IsCtx ctx => ctx -> Word64 -> Snap (ReqObject ctx) Source #

(.!) :: (IsCtx ctx, FromJSON x) => ReqObject ctx -> Text -> Snap x Source #

Like (.!?) but returns a 422 error (with errorEarly) if the key isn't present

(.!?) :: (IsCtx ctx, FromJSON x) => ReqObject ctx -> Text -> Snap (Maybe x) Source #

Get a JSON value from the request object, and give a HTTP 422 response (errorEarly) if the value is malformed (not able to be decoded). If it's not present, don't fail: just give us a Nothing

data ReqObject ctx Source #

Constructors

ReqObject ctx (HashMap Text Value) 

Errors

errorEarlyCode :: ApiErr ae => ae -> Snap x Source #

NOTE: be very careful to not use this with any setup/teardown block like withTransaction - causes resource leaks - BUT! This should never happen to you because all your DB code should use inTransaction!

NOTE: use 403 forbidden instead of unauthorized - unauth means not logged in at all

Also note this returns any 'Snap x' so you can use it like a throw anywhere in your snap code

class ApiErr apiErr where Source #

Methods

errResult :: apiErr -> ErrResult Source #

apiErr_missingRequestKey :: Text -> apiErr Source #

The request object is missing a required key. E.g. the request is {"first": Tom} but we need both a "first" and a "last"

apiErr_requestNotJSON :: apiErr Source #

We can't process the request because the request is malformed JSON or not JSON at all

apiErr_requestNotJSONObject :: apiErr Source #

The request *is* JSON, but not an object (e.g. maybe it's an array or a number, but we need an object)

apiErr_malformedRequestValue :: Text -> Value -> apiErr Source #

It's a JSON object but it's malformed somehow (e.g. maybe it's got the wrong keys). In other words, we can't fromJSON it successfully.

(The Text is the key of the malformed value)

apiErr_unexpectedError :: Text -> apiErr Source #

A 500 internal server error

apiErr_inReadOnlyMode :: apiErr Source #

data ErrResult Source #

Constructors

ErrResult Status Value 
Instances
Eq ErrResult Source # 
Instance details

Defined in Gingersnap.Core

Show ErrResult Source # 
Instance details

Defined in Gingersnap.Core

ctxErr :: IsCtx ctx => ctx -> CtxErrType ctx -> CtxErrType ctx Source #

Internals

data RspPayload Source #

Constructors

ToJSON x => RspPayload_Good x 
ApiErr e => RspPayload_Bad e 
RspPayload_Custom Status ByteString ByteString

First ByteString is MIME type; second is response body

RspPayload_Empty 

Reexports, for convenience

data Pool a #

Instances
Show (Pool a) 
Instance details

Defined in Data.Pool

Methods

showsPrec :: Int -> Pool a -> ShowS #

show :: Pool a -> String #

showList :: [Pool a] -> ShowS #

createPool #

Arguments

:: IO a

Action that creates a new resource.

-> (a -> IO ())

Action that destroys an existing resource.

-> Int

The number of stripes (distinct sub-pools) to maintain. The smallest acceptable value is 1.

-> NominalDiffTime

Amount of time for which an unused resource is kept open. The smallest acceptable value is 0.5 seconds.

The elapsed time before destroying a resource may be a little longer than requested, as the reaper thread wakes at 1-second intervals.

-> Int

Maximum number of resources to keep open per stripe. The smallest acceptable value is 1.

Requests for resources will block if this limit is reached on a single stripe, even if other stripes have idle resources available.

-> IO (Pool a) 

Create a striped resource pool.

Although the garbage collector will destroy all idle resources when the pool is garbage collected it's recommended to manually destroyAllResources when you're done with the pool so that the resources are freed up as soon as possible.

data Connection #

Instances
Eq Connection 
Instance details

Defined in Database.PostgreSQL.Simple.Internal