hyperbole-0.2.0: Web Framework inspired by HTMX
Safe HaskellSafe-Inferred
LanguageGHC2021

Web.Hyperbole.Route

Synopsis

Documentation

data Path Source #

Constructors

Path 

Fields

Instances

Instances details
IsString Path Source # 
Instance details

Defined in Web.Hyperbole.Route

Methods

fromString :: String -> Path #

Show Path Source # 
Instance details

Defined in Web.Hyperbole.Route

Methods

showsPrec :: Int -> Path -> ShowS #

show :: Path -> String #

showList :: [Path] -> ShowS #

class Route a where Source #

Minimal complete definition

Nothing

Methods

matchRoute :: Path -> Maybe a Source #

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

routePath :: a -> Path Source #

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

defRoute :: a Source #

default defRoute :: (Generic a, GenRoute (Rep a)) => 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 => [Text] -> Maybe a Source #

Use the default route if it's empty

class GenRoute f where Source #

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 #