Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module builds on Spock's "reroute" library by associating a GHC.OverloadedLabels label to each route, which views can then use to reverse routes in a type-safe manner. It also uses some rediculous function chaining to almost create an indexed monad, but not quite because I can't figure out quite how to make that work. A fairly function example follows:
First, we'll define a couple of views:
index :: Has "users" lts (Path '[] 'Open) => TsActionCtxT lts xs sess a index =showPath
#users >>= 'Spock.text users :: Has "root" lts (Path '[] 'Open) => TsActionCtxT lts xs sess a users = do root <-showPath
#root text $ "GET users, root is, " <> root usersPost :: TsActionCtxT lts xs sess a usersPost = text "POST to users!"
Then, routing to those views looks like this:
runroute
ropool rwpool $path
#rootroot
(getpost
index) .path
#users "users" (do get users post usersPost)
Notice the (.) after the getpost index
. We're chaining functions together
and then passing that chained function to runroute
in order to generate an
actual Spock RouteM
.
Synopsis
- type RoutingM as lts xs sess = ReaderT (Path as Open, ReadWritePool) (TsSpockCtxT lts xs sess)
- runroute :: (Applicative f, MonadIO m, RouteM t) => ReadOnlyPool -> ReadWritePool -> ((ReadWritePool, Rec '[], f ()) -> (ReadWritePool, Rec lts, t (Context lts '[ReadOnlyPool]) m ())) -> t ctx m ()
- path :: (KnownNat ((RecSize (Sort ((l := Path as Open) ': lts)) - RecTyIdxH 0 l (Sort ((l := Path as Open) ': lts))) - 1), RecCopy lts lts (Sort ((l := Path as Open) ': lts)), KnownNat (RecSize lts), KeyDoesNotExist l lts, KnownSymbol l) => FldProxy l -> Path as Open -> RoutingM as lts0 xs sess a -> (ReadWritePool, Rec lts, TsSpockCtxT lts0 xs sess a) -> (ReadWritePool, Record ((l := Path as Open) ': lts), TsSpockCtxT lts0 xs sess a)
- dbwrite :: RoutingM as lts (ReadWritePool ': xs) sess () -> RoutingM as lts xs sess ()
- getpost :: HasRep as => HVectElim as (TsActionCtxT lts xs sess ()) -> RoutingM as lts xs sess ()
- get :: HasRep as => HVectElim as (TsActionCtxT lts xs sess ()) -> RoutingM as lts xs sess ()
- post :: HasRep as => HVectElim as (TsActionCtxT lts xs sess ()) -> RoutingM as lts xs sess ()
Documentation
type RoutingM as lts xs sess = ReaderT (Path as Open, ReadWritePool) (TsSpockCtxT lts xs sess) Source #
Reader monad to pass one Path
to potentially multiple
different 'get'/'post'/etc calls.
:: (Applicative f, MonadIO m, RouteM t) | |
=> ReadOnlyPool | Read-only postgres connection pool |
-> ReadWritePool | Read-write postgres connection pool |
-> ((ReadWritePool, Rec '[], f ()) -> (ReadWritePool, Rec lts, t (Context lts '[ReadOnlyPool]) m ())) | Chain of functions built up using |
-> t ctx m () |
Convert a chain of path
calls into a RouteM
instance. This takes a ReadOnlyPool
and a
ReadWritePool
in order to operate the
auth
and dbwrite
calls.
:: (KnownNat ((RecSize (Sort ((l := Path as Open) ': lts)) - RecTyIdxH 0 l (Sort ((l := Path as Open) ': lts))) - 1), RecCopy lts lts (Sort ((l := Path as Open) ': lts)), KnownNat (RecSize lts), KeyDoesNotExist l lts, KnownSymbol l) | |
=> FldProxy l | Label for this URL path |
-> Path as Open |
|
-> RoutingM as lts0 xs sess a | |
-> (ReadWritePool, Rec lts, TsSpockCtxT lts0 xs sess a) | |
-> (ReadWritePool, Record ((l := Path as Open) ': lts), TsSpockCtxT lts0 xs sess a) |
Describe a path for routing. This both builds up the
RouteM
monad and associates the given label with the
URL so that views can look up the URL using showPath
&c.
dbwrite :: RoutingM as lts (ReadWritePool ': xs) sess () -> RoutingM as lts xs sess () Source #
Raise up a RoutingM
to have ReadWritePool
in its
extras record.
getpost :: HasRep as => HVectElim as (TsActionCtxT lts xs sess ()) -> RoutingM as lts xs sess () Source #
Run this view whether the client did a GET or a POST request
get :: HasRep as => HVectElim as (TsActionCtxT lts xs sess ()) -> RoutingM as lts xs sess () Source #
Run this view only on GET requests
post :: HasRep as => HVectElim as (TsActionCtxT lts xs sess ()) -> RoutingM as lts xs sess () Source #
Run this view only on POST requests