Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- rspGood :: ToJSON x => x -> Rsp
- rspBad :: ApiErr ae => ae -> Rsp
- rspBadCommit :: ApiErr ae => ae -> Rsp
- rspBadRollback :: ApiErr ae => ae -> Rsp
- rspGoodCSV :: ByteString -> Rsp
- rspGoodLBS :: ByteString -> ByteString -> Rsp
- rspEmptyGood :: Rsp
- data Rsp = Rsp {}
- pureRsp :: IsCtx ctx => ctx -> Rsp -> Snap ()
- inTransaction :: IsCtx ctx => ctx -> (Connection -> IO Rsp) -> Snap ()
- inTransactionMode :: IsCtx ctx => ctx -> IsolationLevel -> ReadWriteMode -> (Connection -> IO Rsp) -> Snap ()
- inTransaction_readOnly :: IsCtx ctx => ctx -> (Connection -> IO Rsp) -> Snap ()
- inTransaction_override :: IsCtx ctx => ctx -> (Connection -> IO Rsp) -> Snap ()
- rspIsGood :: Rsp -> Bool
- class ApiErr (CtxErrType ctx) => IsCtx ctx where
- type CtxErrType ctx
- ctxConnectionPool :: ctx -> Pool Connection
- ctxGetReadOnlyMode :: ctx -> IO Bool
- ctx_wrapSuccess :: ToJSON x => ctx -> x -> Value
- reqObject :: IsCtx ctx => ctx -> Snap (ReqObject ctx)
- reqObject' :: IsCtx ctx => ctx -> Word64 -> Snap (ReqObject ctx)
- (.!) :: (IsCtx ctx, FromJSON x) => ReqObject ctx -> Text -> Snap x
- (.!?) :: (IsCtx ctx, FromJSON x) => ReqObject ctx -> Text -> Snap (Maybe x)
- data ReqObject ctx = ReqObject ctx (HashMap Text Value)
- errorEarlyCode :: ApiErr ae => ae -> Snap x
- class ApiErr apiErr where
- errResult :: apiErr -> ErrResult
- apiErr_missingRequestKey :: Text -> apiErr
- apiErr_requestNotJSON :: apiErr
- apiErr_requestNotJSONObject :: apiErr
- apiErr_malformedRequestValue :: Text -> Value -> apiErr
- apiErr_unexpectedError :: Text -> apiErr
- apiErr_inReadOnlyMode :: apiErr
- data ErrResult = ErrResult Status Value
- data DefaultApiErr
- ctxErr :: IsCtx ctx => ctx -> CtxErrType ctx -> CtxErrType ctx
- data RspPayload
- = forall x.ToJSON x => RspPayload_Good x
- | forall e.ApiErr e => RspPayload_Bad e
- | RspPayload_Custom Status ByteString ByteString
- | RspPayload_Empty
- data ShouldCommitOrRollback
- data Pool a
- createPool :: IO a -> (a -> IO ()) -> Int -> NominalDiffTime -> Int -> IO (Pool a)
- data Connection
Rsp
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
rspBadRollback :: ApiErr ae => ae -> Rsp Source #
The same as rspBad
but more explicit that we roll back
rspGoodCSV :: ByteString -> Rsp Source #
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
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 # | |
Generic Rsp Source # | |
NFData Rsp Source # | |
Defined in Gingersnap.Core | |
type Rep Rsp Source # | |
Defined in Gingersnap.Core type Rep Rsp = D1 ('MetaData "Rsp" "Gingersnap.Core" "gingersnap-0.2.2.3-1cBbVyzm2okBmXGf2oXMQO" 'False) (C1 ('MetaCons "Rsp" 'PrefixI 'True) (S1 ('MetaSel ('Just "rspShouldCommit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShouldCommitOrRollback) :*: S1 ('MetaSel ('Just "rspPayload") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RspPayload))) |
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!_
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
type CtxErrType ctx Source #
type CtxErrType ctx = DefaultApiErr
ctxConnectionPool :: ctx -> Pool Connection Source #
ctxGetReadOnlyMode :: ctx -> IO Bool Source #
ctx_wrapSuccess :: ToJSON x => ctx -> x -> Value Source #
JSON requests
(.!) :: (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
Errors
errorEarlyCode :: ApiErr ae => ae -> Snap x Source #
This returns any 'Snap x' so you can use it like a throw anywhere in your snap code
NOTE: if you ever use 's withTransaction
(which we don't recommend!)
this function has the same caveats as finishWith
class ApiErr apiErr where Source #
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
The Text value is the error message. You may want different behavior in development vs. production, e.g. not showing internal errors in prod
apiErr_inReadOnlyMode :: apiErr Source #
Instances
data DefaultApiErr Source #
Instances
Eq DefaultApiErr Source # | |
Defined in Gingersnap.Core (==) :: DefaultApiErr -> DefaultApiErr -> Bool # (/=) :: DefaultApiErr -> DefaultApiErr -> Bool # | |
Show DefaultApiErr Source # | |
Defined in Gingersnap.Core showsPrec :: Int -> DefaultApiErr -> ShowS # show :: DefaultApiErr -> String # showList :: [DefaultApiErr] -> ShowS # | |
ApiErr DefaultApiErr Source # | |
Defined in Gingersnap.Core errResult :: DefaultApiErr -> ErrResult Source # apiErr_missingRequestKey :: Text -> DefaultApiErr Source # apiErr_requestNotJSON :: DefaultApiErr Source # apiErr_requestNotJSONObject :: DefaultApiErr Source # apiErr_malformedRequestValue :: Text -> Value -> DefaultApiErr Source # |
ctxErr :: IsCtx ctx => ctx -> CtxErrType ctx -> CtxErrType ctx Source #
Internals
data RspPayload Source #
forall x.ToJSON x => RspPayload_Good x | |
forall e.ApiErr e => RspPayload_Bad e | |
RspPayload_Custom Status ByteString ByteString | First ByteString is MIME type; second is response body |
RspPayload_Empty |
Instances
NFData RspPayload Source # | |
Defined in Gingersnap.Core rnf :: RspPayload -> () # |
data ShouldCommitOrRollback Source #
Instances
Eq ShouldCommitOrRollback Source # | |
Defined in Gingersnap.Core | |
Show ShouldCommitOrRollback Source # | |
Defined in Gingersnap.Core showsPrec :: Int -> ShouldCommitOrRollback -> ShowS # show :: ShouldCommitOrRollback -> String # showList :: [ShouldCommitOrRollback] -> ShowS # | |
Generic ShouldCommitOrRollback Source # | |
Defined in Gingersnap.Core type Rep ShouldCommitOrRollback :: Type -> Type # | |
NFData ShouldCommitOrRollback Source # | |
Defined in Gingersnap.Core rnf :: ShouldCommitOrRollback -> () # | |
type Rep ShouldCommitOrRollback Source # | |
Defined in Gingersnap.Core |
Reexports, for convenience
:: 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 | |
Defined in Database.PostgreSQL.Simple.Internal (==) :: Connection -> Connection -> Bool # (/=) :: Connection -> Connection -> Bool # |