hyperbole-0.3.5: Interactive HTML apps using type-safe serverside Haskell
Safe HaskellSafe-Inferred
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
 = HomePage
 | Users
 | User Int
 deriving (Generic, Route)

/         -> HomePage
/users/   -> Users
/user/100 -> User 100

Minimal complete definition

Nothing

Methods

defRoute :: a Source #

The default route to use if attempting to match on empty segments

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

routePath :: a -> [Segment] Source #

Map a route to segments

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

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

Try to match segments to a route

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

Instances

Instances details
Route Text Source # 
Instance details

Defined in Web.Hyperbole.Route

Route String Source # 
Instance details

Defined in Web.Hyperbole.Route

Route Integer Source # 
Instance details

Defined in Web.Hyperbole.Route

Route Int Source # 
Instance details

Defined in Web.Hyperbole.Route

Route a => Route (Maybe a) Source # 
Instance details

Defined in Web.Hyperbole.Route

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 where Source #

Automatically derive Route

Methods

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

genPaths :: f p -> [Text] Source #

genFirst :: f p Source #

Instances

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

Defined in Web.Hyperbole.Route

Methods

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

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

genFirst :: forall (p :: k0). U1 p Source #

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

Defined in Web.Hyperbole.Route

Methods

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

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

genFirst :: forall (p :: k0). (a :*: b) p Source #

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

Defined in Web.Hyperbole.Route

Methods

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

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

genFirst :: forall (p :: k0). (a :+: b) p Source #

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

Defined in Web.Hyperbole.Route

Methods

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

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

genFirst :: forall (p :: k0). K1 R sub p Source #

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

Defined in Web.Hyperbole.Route

Methods

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

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

genFirst :: forall (p :: k0). M1 C c f p Source #

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

Defined in Web.Hyperbole.Route

Methods

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

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

genFirst :: forall (p :: k0). M1 D c f p Source #

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

Defined in Web.Hyperbole.Route

Methods

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

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

genFirst :: forall (p :: k0). M1 S c f p Source #

genRouteRead :: 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 #

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 #