hyperbole-0.4.2: Interactive HTML apps using type-safe serverside Haskell
Safe HaskellNone
LanguageGHC2021

Web.Hyperbole.Route

Synopsis

Documentation

class Route a where Source #

Derive this class to use a sum type as a route. Constructors and Selectors map intuitively to url patterns

data AppRoute
  = Main
  | Messages
  | User UserId
  deriving (Eq, Generic)

instance Route AppRoute where
  baseRoute = Just Main
>>> routeUrl Main
/
>>> routeUrl (User 9)
/user/9

Minimal complete definition

Nothing

Methods

baseRoute :: Maybe a Source #

The route to use if attempting to match on empty segments

default baseRoute :: (Generic a, GenRoute (Rep a)) => Maybe a Source #

matchRoute :: [Segment] -> Maybe a Source #

Try to match segments to a route

default matchRoute :: (Generic a, GenRoute (Rep a)) => [Segment] -> Maybe a Source #

routePath :: a -> [Segment] Source #

Map a route to segments

default routePath :: (Generic a, Eq a, GenRoute (Rep a)) => a -> [Segment] Source #

findRoute :: Route a => [Segment] -> Maybe a Source #

Try to match a route, use defRoute if it's empty

routeUrl :: Route a => a -> Url Source #

Convert a Route to a Url

>>> routeUrl (User 100)
/user/100

class GenRoute (f :: k -> Type) where Source #

Automatically derive Route

Methods

genRoute :: forall (p :: k). [Text] -> Maybe (f p) Source #

genPaths :: forall (p :: k). f p -> [Text] Source #

Instances

Instances details
GenRoute (U1 :: k -> Type) Source # 
Instance details

Defined in Web.Hyperbole.Route

Methods

genRoute :: forall (p :: k). [Text] -> Maybe (U1 p) Source #

genPaths :: forall (p :: k). U1 p -> [Text] Source #

(GenRoute a, GenRoute b) => GenRoute (a :*: b :: k -> Type) Source # 
Instance details

Defined in Web.Hyperbole.Route

Methods

genRoute :: forall (p :: k). [Text] -> Maybe ((a :*: b) p) Source #

genPaths :: forall (p :: k). (a :*: b) p -> [Text] Source #

(GenRoute a, GenRoute b) => GenRoute (a :+: b :: k -> Type) Source # 
Instance details

Defined in Web.Hyperbole.Route

Methods

genRoute :: forall (p :: k). [Text] -> Maybe ((a :+: b) p) Source #

genPaths :: forall (p :: k). (a :+: b) p -> [Text] Source #

Route sub => GenRoute (K1 R sub :: k -> Type) Source # 
Instance details

Defined in Web.Hyperbole.Route

Methods

genRoute :: forall (p :: k). [Text] -> Maybe (K1 R sub p) Source #

genPaths :: forall (p :: k). K1 R sub p -> [Text] Source #

(Constructor c, GenRoute f) => GenRoute (M1 C c f :: k -> Type) Source # 
Instance details

Defined in Web.Hyperbole.Route

Methods

genRoute :: forall (p :: k). [Text] -> Maybe (M1 C c f p) Source #

genPaths :: forall (p :: k). M1 C c f p -> [Text] Source #

GenRoute f => GenRoute (M1 D c f :: k -> Type) Source # 
Instance details

Defined in Web.Hyperbole.Route

Methods

genRoute :: forall (p :: k). [Text] -> Maybe (M1 D c f p) Source #

genPaths :: forall (p :: k). M1 D c f p -> [Text] Source #

GenRoute f => GenRoute (M1 S c f :: k -> Type) Source # 
Instance details

Defined in Web.Hyperbole.Route

Methods

genRoute :: forall (p :: k). [Text] -> Maybe (M1 S c f p) Source #

genPaths :: forall (p :: k). M1 S c f p -> [Text] Source #

genRouteRead :: forall {k} x (a :: k). Read x => [Text] -> Maybe (K1 R x a) Source #

data Url #

Instances

Instances details
IsString Url 
Instance details

Defined in Web.View.Types.Url

Methods

fromString :: String -> Url #

Monoid Url 
Instance details

Defined in Web.View.Types.Url

Methods

mempty :: Url #

mappend :: Url -> Url -> Url #

mconcat :: [Url] -> Url #

Semigroup Url 
Instance details

Defined in Web.View.Types.Url

Methods

(<>) :: Url -> Url -> Url #

sconcat :: NonEmpty Url -> Url #

stimes :: Integral b => b -> Url -> Url #

Read Url 
Instance details

Defined in Web.View.Types.Url

Show Url 
Instance details

Defined in Web.View.Types.Url

Methods

showsPrec :: Int -> Url -> ShowS #

show :: Url -> String #

showList :: [Url] -> ShowS #

Eq Url 
Instance details

Defined in Web.View.Types.Url

Methods

(==) :: Url -> Url -> Bool #

(/=) :: Url -> Url -> Bool #