Shpadoinkle-router-0.3.0.1: A single page application rounter for Shpadoinkle based on Servant.

Safe HaskellNone
LanguageHaskell2010

Shpadoinkle.Router

Contents

Description

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

Classes

class HasRouter layout where Source #

This type class traverses the Servant API and sets up a function to build its term level representation.

Associated Types

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.

Methods

route :: (layout :>> route) -> Router route Source #

Instances
HasRouter Raw Source # 
Instance details

Defined in Shpadoinkle.Router

Associated Types

type Raw :>> route :: Type Source #

Methods

route :: (Raw :>> route) -> Router route Source #

HasRouter (RawM' serverType) Source # 
Instance details

Defined in Shpadoinkle.Router

Associated Types

type (RawM' serverType) :>> route :: Type Source #

Methods

route :: (RawM' serverType :>> route) -> Router route Source #

HasRouter (f (HTML ': ([] :: [Type])) (Html m b)) Source # 
Instance details

Defined in Shpadoinkle.Router

Associated Types

type (f (HTML ': []) (Html m b)) :>> route :: Type Source #

Methods

route :: (f (HTML ': []) (Html m b) :>> route) -> Router route Source #

(HasRouter x, HasRouter y) => HasRouter (x :<|> y) Source # 
Instance details

Defined in Shpadoinkle.Router

Associated Types

type (x :<|> y) :>> route :: Type Source #

Methods

route :: ((x :<|> y) :>> route) -> Router route Source #

HasRouter (View m b) Source # 
Instance details

Defined in Shpadoinkle.Router

Associated Types

type (View m b) :>> route :: Type Source #

Methods

route :: (View m b :>> route) -> Router route Source #

(HasRouter sub, FromHttpApiData x, KnownSymbol sym) => HasRouter (QueryParam sym x :> sub) Source # 
Instance details

Defined in Shpadoinkle.Router

Associated Types

type (QueryParam sym x :> sub) :>> route :: Type Source #

Methods

route :: ((QueryParam sym x :> sub) :>> route) -> Router route Source #

(HasRouter sub, FromHttpApiData x, KnownSymbol sym) => HasRouter (QueryParam' (Required ': ([] :: [Type])) sym x :> sub) Source # 
Instance details

Defined in Shpadoinkle.Router

Associated Types

type (QueryParam' (Required ': []) sym x :> sub) :>> route :: Type Source #

Methods

route :: ((QueryParam' (Required ': []) sym x :> sub) :>> route) -> Router route Source #

(HasRouter sub, FromHttpApiData x, KnownSymbol sym) => HasRouter (QueryParams sym x :> sub) Source # 
Instance details

Defined in Shpadoinkle.Router

Associated Types

type (QueryParams sym x :> sub) :>> route :: Type Source #

Methods

route :: ((QueryParams sym x :> sub) :>> route) -> Router route Source #

(HasRouter sub, KnownSymbol sym) => HasRouter (QueryFlag sym :> sub) Source # 
Instance details

Defined in Shpadoinkle.Router

Associated Types

type (QueryFlag sym :> sub) :>> route :: Type Source #

Methods

route :: ((QueryFlag sym :> sub) :>> route) -> Router route Source #

(HasRouter sub, FromHttpApiData x) => HasRouter (Capture sym x :> sub) Source # 
Instance details

Defined in Shpadoinkle.Router

Associated Types

type (Capture sym x :> sub) :>> route :: Type Source #

Methods

route :: ((Capture sym x :> sub) :>> route) -> Router route Source #

(HasRouter sub, KnownSymbol path) => HasRouter (path :> sub) Source # 
Instance details

Defined in Shpadoinkle.Router

Associated Types

type (path :> sub) :>> route :: Type Source #

Methods

route :: ((path :> sub) :>> route) -> Router route Source #

class Routed a r where Source #

Ensure global coherence between routes and the api

Methods

redirect :: r -> Redirect a Source #

Types

data Redirect api Source #

Redirect is an existentialized Proxy that must be a member of the API

Constructors

(IsElem sub api, HasLink sub) => Redirect (Proxy sub) (MkLink sub Link -> Link) 

data Router a where Source #

Term level API representation

Constructors

RChoice :: Router a -> Router a -> Router a 
RCapture :: (Text -> Either Text x) -> (x -> Router a) -> Router a 
RQueryParam :: KnownSymbol sym => (Text -> Either Text x) -> Proxy sym -> (Maybe x -> Router a) -> Router a 
RQueryParamR :: KnownSymbol sym => (Text -> Either Text x) -> Proxy sym -> (x -> Router a) -> Router a 
RQueryParams :: KnownSymbol sym => (Text -> Either Text x) -> 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 

data View :: (Type -> Type) -> Type -> Type Source #

Servant terminal for Shpadoinkle views (recommended)

Instances
HasLink (View m a :: Type) Source # 
Instance details

Defined in Shpadoinkle.Router

Associated Types

type MkLink (View m a) a :: Type Source #

Methods

toLink :: (Link -> a0) -> Proxy (View m a) -> Link -> MkLink (View m a) a0 Source #

HasServer (View m a :: Type) context Source # 
Instance details

Defined in Shpadoinkle.Router

Associated Types

type ServerT (View m a) m :: Type Source #

Methods

route :: Proxy (View m a) -> Context context -> Delayed env (Server (View m a)) -> Router env Source #

hoistServerWithContext :: Proxy (View m a) -> Proxy context -> (forall x. m0 x -> n x) -> ServerT (View m a) m0 -> ServerT (View m a) n Source #

HasRouter (View m b) Source # 
Instance details

Defined in Shpadoinkle.Router

Associated Types

type (View m b) :>> route :: Type Source #

Methods

route :: (View m b :>> route) -> Router route Source #

ServeRouter (View n b) r m a Source # 
Instance details

Defined in Shpadoinkle.Router.Server

Methods

serveUIUnsafe :: FilePath -> (r -> IO (Html m a)) -> (View n b :>> r) -> Server (View n b) Source #

type MkLink (View m a :: Type) b Source # 
Instance details

Defined in Shpadoinkle.Router

type MkLink (View m a :: Type) b = b
type ServerT (View m a :: Type) n Source # 
Instance details

Defined in Shpadoinkle.Router

type ServerT (View m a :: Type) n = ServerT RawM n
type (View m b) :>> a Source # 
Instance details

Defined in Shpadoinkle.Router

type (View m b) :>> a = a

data HTML :: Type Source #

A Mime type for rendering Html as "text/html"

Instances
Accept HTML Source # 
Instance details

Defined in Shpadoinkle.Router

MimeRender HTML (Html m a) Source # 
Instance details

Defined in Shpadoinkle.Router

HasRouter (f (HTML ': ([] :: [Type])) (Html m b)) Source # 
Instance details

Defined in Shpadoinkle.Router

Associated Types

type (f (HTML ': []) (Html m b)) :>> route :: Type Source #

Methods

route :: (f (HTML ': []) (Html m b) :>> route) -> Router route Source #

type (f (HTML ': ([] :: [Type])) (Html m b)) :>> a Source # 
Instance details

Defined in Shpadoinkle.Router

type (f (HTML ': ([] :: [Type])) (Html m b)) :>> a = a

Shpadoinkle with SPA

fullPageSPAC Source #

Arguments

:: HasRouter layout 
=> Backend b m a 
=> Monad (b m) 
=> Eq a 
=> NFData 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.

fullPageSPA Source #

Arguments

:: HasRouter layout 
=> Backend b m a 
=> Monad (b m) 
=> Eq a 
=> NFData 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.

fullPageSPA' Source #

Arguments

:: HasRouter layout 
=> Backend b m a 
=> Monad (b m) 
=> Eq a 
=> NFData a 
=> Functor m 
=> (m ~> JSM)

how do we get to JSM?

-> (TVar a -> b m ~> m)

what backend are we running?

-> TVar a

where do we store the state?

-> (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.

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.

getURI :: forall a r. Routed a r => r -> URI Source #

Get the cannonical URI for a given route

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

data Raw Source #

Endpoint for plugging in your own Wai Applications.

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 Applications, 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 # 
Instance details

Defined in Shpadoinkle.Router

Associated Types

type Raw :>> route :: Type Source #

Methods

route :: (Raw :>> route) -> Router route Source #

RunClient m => HasClient m Raw

Pick a Method and specify where the server you want to query is. You get back the full ResponseF.

Instance details

Defined in Servant.Client.Core.HasClient

Associated Types

type Client m Raw :: Type Source #

Methods

clientWithRoute :: Proxy m -> Proxy Raw -> Request -> Client m Raw Source #

hoistClientMonad :: Proxy m -> Proxy Raw -> (forall x. mon x -> mon' x) -> Client mon Raw -> Client mon' Raw Source #

ServeRouter Raw r m a Source # 
Instance details

Defined in Shpadoinkle.Router.Server

Methods

serveUIUnsafe :: FilePath -> (r -> IO (Html m a)) -> (Raw :>> r) -> Server Raw Source #

HasLink Raw 
Instance details

Defined in Servant.Links

Associated Types

type MkLink Raw a :: Type Source #

Methods

toLink :: (Link -> a) -> Proxy Raw -> Link -> MkLink Raw a Source #

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"
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT Raw m :: Type Source #

Methods

route :: Proxy Raw -> Context context -> Delayed env (Server Raw) -> Router env Source #

hoistServerWithContext :: Proxy Raw -> Proxy context -> (forall x. m x -> n x) -> ServerT Raw m -> ServerT Raw n Source #

type Client m Raw 
Instance details

Defined in Servant.Client.Core.HasClient

type Client m Raw = Method -> m Response
type Raw :>> a Source # 
Instance details

Defined in Shpadoinkle.Router

type Raw :>> a = a
type MkLink Raw a 
Instance details

Defined in Servant.Links

type MkLink Raw a = a
type ServerT Raw m 
Instance details

Defined in Servant.Server.Internal

data RawM' serverType Source #

This is a type to use to define a Servant API. It signifies a route that allows embedding of a WAI Application. It is similar to Raw, but it has a HasServer instance that allows embedding of monadic effects. This should be more convenient than Raw.

The phantom type serverType is used for defining the HasDocs instance. There are instances for HasClient and HasServer for RawM' with a polymorphic phantom type, but there is only a HasDocs instance specified for RawM' FileServer. This allows the end-user to easily create a HasDocs instance for a custom Application.

Instances
HasRouter (RawM' serverType) Source # 
Instance details

Defined in Shpadoinkle.Router

Associated Types

type (RawM' serverType) :>> route :: Type Source #

Methods

route :: (RawM' serverType :>> route) -> Router route Source #

HasLink (RawM' st :: Type) 
Instance details

Defined in Servant.RawM

Associated Types

type MkLink (RawM' st) a :: Type Source #

Methods

toLink :: (Link -> a) -> Proxy (RawM' st) -> Link -> MkLink (RawM' st) a Source #

type (RawM' serverType) :>> a Source # 
Instance details

Defined in Shpadoinkle.Router

type (RawM' serverType) :>> a = a
type MkLink (RawM' st :: Type) a 
Instance details

Defined in Servant.RawM

type MkLink (RawM' st :: Type) a = a
type ServerT (RawM' serverType :: Type) m 
Instance details

Defined in Servant.RawM.Server

type ServerT (RawM' serverType :: Type) m = m Application

type RawM = RawM' FileServer Source #

Specialization of RawM' to FileServer. This can be used if you are using serveDirectoryWebApp, serveDirectoryFileServer, etc.

class (Applicative m, MonadIO m) => MonadJSM (m :: Type -> Type) Source #

The MonadJSM is to JSM what MonadIO is to IO. When using GHCJS it is MonadIO.

Instances
MonadJSM JSM 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> JSM a Source #

MonadJSM ClientM 
Instance details

Defined in Servant.Client.JS

Methods

liftJSM' :: JSM a -> ClientM a Source #

MonadJSM m => MonadJSM (MaybeT m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> MaybeT m a Source #

MonadJSM m => MonadJSM (ListT m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> ListT m a Source #

MonadJSM m => MonadJSM (IdentityT m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> IdentityT m a Source #

MonadJSM m => MonadJSM (ExceptT e m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> ExceptT e m a Source #

(Error e, MonadJSM m) => MonadJSM (ErrorT e m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> ErrorT e m a Source #

MonadJSM m => MonadJSM (StateT s m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> StateT s m a Source #

(Monoid w, MonadJSM m) => MonadJSM (WriterT w m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> WriterT w m a Source #

MonadJSM m => MonadJSM (StateT s m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> StateT s m a Source #

MonadJSM m => MonadJSM (ReaderT r m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> ReaderT r m a Source #

(Monoid w, MonadJSM m) => MonadJSM (WriterT w m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> WriterT w m a Source #

MonadJSM m => MonadJSM (ContT r m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> ContT r m a Source #

(Monoid w, MonadJSM m) => MonadJSM (RWST r w s m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> RWST r w s m a Source #

(Monoid w, MonadJSM m) => MonadJSM (RWST r w s m) 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

liftJSM' :: JSM a -> RWST r w s m a Source #

class HasLink (endpoint :: k) where Source #

Construct a toLink for an endpoint.

Associated Types

type MkLink (endpoint :: k) a :: Type Source #

Methods

toLink Source #

Arguments

:: (Link -> a) 
-> Proxy endpoint

The API endpoint you would like to point to

-> Link 
-> MkLink endpoint a 

Sub route utilities

class TraverseUnions m layout b where Source #

Methods

traverseUnions :: (SwitchInput layout -> m b) -> layout -> m (SwitchOutput layout b) Source #

Instances
(SwitchOutput a b ~ b, SwitchInput a ~ a) => TraverseUnions m a b Source # 
Instance details

Defined in Shpadoinkle.Router

Methods

traverseUnions :: (SwitchInput a -> m b) -> a -> m (SwitchOutput a b) Source #

(Applicative m, TraverseUnions m r b, SwitchInput (a :<|> r) ~ a, SwitchInput r ~ a, SwitchOutput (a :<|> r) b ~ (b :<|> SwitchOutput r b)) => TraverseUnions m (a :<|> r) b Source # 
Instance details

Defined in Shpadoinkle.Router

Methods

traverseUnions :: (SwitchInput (a :<|> r) -> m b) -> (a :<|> r) -> m (SwitchOutput (a :<|> r) b) Source #

(Applicative m, TraverseUnions m r b, TraverseUnions m as b, SwitchInput r ~ a, SwitchInput as ~ a) => TraverseUnions m ((a :<|> as) :<|> r) b Source # 
Instance details

Defined in Shpadoinkle.Router

Methods

traverseUnions :: (SwitchInput ((a :<|> as) :<|> r) -> m b) -> ((a :<|> as) :<|> r) -> m (SwitchOutput ((a :<|> as) :<|> r) b) Source #

mapUnions :: TraverseUnions Identity a b => (SwitchInput a -> b) -> a -> SwitchOutput a b Source #