Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides for Servant-based routing for Shpadoinkle applications.
The technique in use is standard for Servant. We have a GADT Router
and some
type class inductive programming with class HasRouter
. The Router
the term
necessary for the runtime operation of single page application routing.
State changes are tracked by the "popstate" event and an MVar ()
. Ideally this is
done via the browser's native APIs only and not an MVar
, however that approach is
blocked by a bug in GHCjs which is documented here.
Synopsis
- class HasRouter layout where
- class Routed a r where
- data Redirect api = (IsElem sub api, HasLink sub) => Redirect (Proxy sub) (MkLink sub Link -> Link)
- data Router a where
- RChoice :: Router a -> Router a -> Router a
- RCapture :: FromHttpApiData x => (x -> Router a) -> Router a
- RQueryParam :: (FromHttpApiData x, KnownSymbol sym) => Proxy sym -> (Maybe x -> Router a) -> Router a
- RQueryParamR :: (FromHttpApiData x, KnownSymbol sym) => Proxy sym -> (x -> Router a) -> Router a
- RQueryParams :: (FromHttpApiData x, KnownSymbol sym) => Proxy sym -> ([x] -> Router a) -> Router a
- RQueryFlag :: KnownSymbol sym => Proxy sym -> (Bool -> Router a) -> Router a
- RPath :: KnownSymbol sym => Proxy sym -> Router a -> Router a
- RView :: a -> Router a
- fullPageSPAC :: forall layout b a r m. HasRouter layout => Backend b m a => Monad (b m) => Eq a => Functor m => (m ~> JSM) -> (TVar a -> b m ~> m) -> (r -> m a) -> (a -> Html (b m) a) -> b m RawNode -> (r -> m (Continuation m a)) -> (layout :>> r) -> JSM ()
- fullPageSPA :: forall layout b a r m. HasRouter layout => Backend b m a => Monad (b m) => Eq a => Functor m => (m ~> JSM) -> (TVar a -> b m ~> m) -> (r -> m a) -> (a -> Html (b m) a) -> b m RawNode -> (r -> m a) -> (layout :>> r) -> JSM ()
- navigate :: forall a m r. MonadJSM m => Routed a r => r -> m ()
- withHydration :: (MonadJSM m, FromJSON a) => (r -> m a) -> r -> m a
- toHydration :: ToJSON a => a -> Html m b
- data Raw
- class (Applicative m, MonadIO m) => MonadJSM (m :: Type -> Type)
- class HasLink (endpoint :: k) where
Classes
class HasRouter layout where Source #
This type class traverses the Servant API and sets up a function to build its term level representation.
type layout :>> route :: Type infixr 4 Source #
:>>
(pronounced "routed as") should be surjective,
as in one route can be the handler for more than one URL.
Instances
HasRouter Raw Source # | |
(HasRouter x, HasRouter y) => HasRouter (x :<|> y) Source # | |
(HasRouter sub, FromHttpApiData x, KnownSymbol sym) => HasRouter (QueryParam sym x :> sub) Source # | |
Defined in Shpadoinkle.Router | |
(HasRouter sub, FromHttpApiData x, KnownSymbol sym) => HasRouter (QueryParam' (Required ': ([] :: [Type])) sym x :> sub) Source # | |
(HasRouter sub, FromHttpApiData x, KnownSymbol sym) => HasRouter (QueryParams sym x :> sub) Source # | |
Defined in Shpadoinkle.Router | |
(HasRouter sub, KnownSymbol sym) => HasRouter (QueryFlag sym :> sub) Source # | |
(HasRouter sub, FromHttpApiData x) => HasRouter (Capture sym x :> sub) Source # | |
(HasRouter sub, KnownSymbol path) => HasRouter (path :> sub) Source # | |
Types
Redirect is an existentialized Proxy that must be a member of the API
Term level API representation
RChoice :: Router a -> Router a -> Router a | |
RCapture :: FromHttpApiData x => (x -> Router a) -> Router a | |
RQueryParam :: (FromHttpApiData x, KnownSymbol sym) => Proxy sym -> (Maybe x -> Router a) -> Router a | |
RQueryParamR :: (FromHttpApiData x, KnownSymbol sym) => Proxy sym -> (x -> Router a) -> Router a | |
RQueryParams :: (FromHttpApiData x, KnownSymbol sym) => Proxy sym -> ([x] -> Router a) -> Router a | |
RQueryFlag :: KnownSymbol sym => Proxy sym -> (Bool -> Router a) -> Router a | |
RPath :: KnownSymbol sym => Proxy sym -> Router a -> Router a | |
RView :: a -> Router a |
Shpadoinkle with SPA
:: HasRouter layout | |
=> Backend b m a | |
=> Monad (b m) | |
=> Eq a | |
=> Functor m | |
=> (m ~> JSM) | how do we get to JSM? |
-> (TVar a -> b m ~> m) | What backend are we running? |
-> (r -> m a) | what is the initial state? |
-> (a -> Html (b m) a) | how should the html look? |
-> b m RawNode | where do we render? |
-> (r -> m (Continuation m a)) | listen for route changes |
-> (layout :>> r) | how shall we relate urls to routes? |
-> JSM () |
This method wraps shpadoinkle
, providing for a convenient entrypoint
for single page applications. It wires together your normal shpadoinkle
app components with a function to respond to route changes and the route mapping
itself. This flavor provides access to the full power of Continuation
in case you
need to handle in-flight updates.
:: HasRouter layout | |
=> Backend b m a | |
=> Monad (b m) | |
=> Eq a | |
=> Functor m | |
=> (m ~> JSM) | how do we get to JSM? |
-> (TVar a -> b m ~> m) | What backend are we running? |
-> (r -> m a) | what is the initial state? |
-> (a -> Html (b m) a) | how should the html look? |
-> b m RawNode | where do we render? |
-> (r -> m a) | listen for route changes |
-> (layout :>> r) | how shall we relate urls to routes? |
-> JSM () |
This method wraps shpadoinkle
, providing for a convenient entrypoint
for single page applications. It wires together your normal shpadoinkle
app components with a function to respond to route changes and the route mapping
itself.
Navigation
navigate :: forall a m r. MonadJSM m => Routed a r => r -> m () Source #
Change the browser's URL to the canonical URL for a given route r
.
Rehydration
withHydration :: (MonadJSM m, FromJSON a) => (r -> m a) -> r -> m a Source #
When using server-side rendering you may benefit from seeding the page with
data. This function get an assumed global variable on the page called "initState".
If it's found, we return that, otherwise we use the provided (r -> m a)
function
to generate the init state for our app, based on the current route. Typically
this is used on the client side.
toHydration :: ToJSON a => a -> Html m b Source #
When using server-side rendering, you may benefit from seeding the page with data. This function returns a script tag that makes a global variable "initState" containing a JSON representation to be used as the initial state of the application on page load. Typically this is used on the server side.
Re-Exports
Endpoint for plugging in your own Wai Application
s.
The given Application
will get the request as received by the server, potentially with
a modified (stripped) pathInfo
if the Application
is being routed with :>
.
In addition to just letting you plug in your existing WAI Application
s,
this can also be used with functions from
Servant.Server.StaticFiles
to serve static files stored in a particular directory on your filesystem
Instances
HasRouter Raw Source # | |
RunClient m => HasClient m Raw | Pick a |
ServeRouter Raw r Source # | |
HasLink Raw | |
HasServer Raw context | Just pass the request to the underlying application and serve its response. Example: type MyApi = "images" :> Raw server :: Server MyApi server = serveDirectory "/var/www/images" |
type Client m Raw | |
Defined in Servant.Client.Core.HasClient | |
type Raw :>> a Source # | |
Defined in Shpadoinkle.Router | |
type MkLink Raw a | |
Defined in Servant.Links | |
type ServerT Raw m | |
Defined in Servant.Server.Internal |
class (Applicative m, MonadIO m) => MonadJSM (m :: Type -> Type) #
Instances
class HasLink (endpoint :: k) where #
Construct a toLink for an endpoint.