| Copyright | (C) 2016-2025 David M. Johnson |
|---|---|
| License | BSD3-style (see the file LICENSE) |
| Maintainer | David M. Johnson <code@dmj.io> |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Miso.Router
Description
This module introduces a Router that produces "correct-by-construction" URL
encoding and decoding from any Haskell algebraic data type. This Router can be used
in conjunction with uriSub or routeSub to perform client-side routing. Further
it also supports the construction of type-safe links in any View model action via
the href_ function exported from this module.
This module can be used in two ways, one is the manual construction of a Router
as seen below.
data Route = Widget Int deriving (Show, Eq) instance Router Route where routeParser = routes [ Widget <$> (path "widget" *> capture) ] fromRoute (Widget value) = [ toPath "widget", toCapture value ] main :: IO () main = print (runRouter "/widget/10" router) > Right (Widget "widget" 10)
The second way is using the Generic deriving mechanism. This should ensure that
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
data Route
= About
| Home
| Widget (Capture "thing" Int) (Path "foo") (Capture "other" MisoString) (QueryParam "bar" Int)
deriving stock (Generic, Show)
deriving anyclass Router
The Generic deriving works by converting the constructor name to a path so
test :: Either RoutingError Route test = toRoute "/widget/23/foo/okay?bar=0"
Decodes as
Right (Widget (Capture 23) (Path "foo") (Capture "okay") (QueryParam (Just 0)))
The order of Capture and Path matters when defined on your sum type. The order of QueryParam and QueryFlag does not.
The router is "reversible" which means it can produce type-safe links using the href_ function.
prettyRoute $ Widget (Capture 23) (Path ("foo")) (Capture ("okay")) (QueryParam (Just 0))
"/widget/23/foo/okay?bar=0"This can be used in conjunction with the href_ field below to embed type safe links into miso View model action code.
button_ [ Miso.Router.href_ (Widget 10) ] [ "click me" ]
Note: the Index constructor is name special, it used to encode the `"/"` path.
data Route = Index deriving stock (Show, Eq) deriving anyclass (Router) main :: IO () main = print (fromRoute Index) -- "/"
Lastly, camel-case constructors only use the first hump of the camel.
data Route = Index | FooBar deriving anyclass Router deriving stock (Show, Eq, Generic) main :: IO () main = print (prettyRoute FooBar) "/foo"
Synopsis
- class Router route where
- fromRoute :: route -> [Token]
- toURI :: route -> URI
- route :: URI -> Either RoutingError route
- href_ :: route -> Attribute action
- prettyRoute :: route -> MisoString
- dumpURI :: route -> MisoString
- toRoute :: MisoString -> Either RoutingError route
- routeParser :: RouteParser route
- type RouteParser = ParserT URI [Token] []
- class GRouter (f :: k -> Type) where
- gFromRoute :: forall (route :: k). f route -> [Token]
- gRouteParser :: forall (route :: k). RouteParser (f route)
- newtype Capture (sym :: k) a = Capture a
- newtype Path (path :: Symbol) = Path MisoString
- newtype QueryParam (path :: Symbol) a = QueryParam (Maybe a)
- newtype QueryFlag (path :: Symbol) = QueryFlag Bool
- data Token
- data URI = URI {}
- data RoutingError
- parseURI :: MisoString -> Either MisoString URI
- prettyURI :: URI -> MisoString
- prettyQueryString :: URI -> MisoString
- runRouter :: MisoString -> RouteParser route -> Either RoutingError route
- routes :: [RouteParser route] -> RouteParser route
- toQueryFlag :: MisoString -> Token
- toQueryParam :: ToMisoString s => MisoString -> s -> Token
- toCapture :: ToMisoString string => string -> Token
- toPath :: MisoString -> Token
- emptyURI :: URI
- queryFlag :: forall (flag :: Symbol). KnownSymbol flag => RouteParser (QueryFlag flag)
- queryParam :: forall (param :: Symbol) a. (FromMisoString a, KnownSymbol param) => RouteParser (QueryParam param a)
- capture :: FromMisoString value => RouteParser value
- path :: MisoString -> RouteParser MisoString
Classes
class Router route where Source #
Class used to facilitate routing for miso applications
Minimal complete definition
Nothing
Methods
fromRoute :: route -> [Token] Source #
toURI :: route -> URI Source #
Convert a 'Router route => route' into a URI
route :: URI -> Either RoutingError route Source #
Map a URI back to a route
href_ :: route -> Attribute action Source #
Convenience for specifying a URL as a hyperlink reference in View
prettyRoute :: route -> MisoString Source #
Route pretty printing
dumpURI :: route -> MisoString Source #
Route debugging
toRoute :: MisoString -> Either RoutingError route Source #
Route parsing from a MisoString
routeParser :: RouteParser route Source #
default routeParser :: (Generic route, GRouter (Rep route)) => RouteParser route Source #
class GRouter (f :: k -> Type) where Source #
Generic deriving for Router
Methods
gFromRoute :: forall (route :: k). f route -> [Token] Source #
gRouteParser :: forall (route :: k). RouteParser (f route) Source #
Instances
| GRouter (U1 :: k -> Type) Source # | |
Defined in Miso.Router Methods gFromRoute :: forall (route :: k). U1 route -> [Token] Source # gRouteParser :: forall (route :: k). RouteParser (U1 route) Source # | |
| (GRouter left, GRouter right) => GRouter (left :*: right :: k -> Type) Source # | |
Defined in Miso.Router Methods gFromRoute :: forall (route :: k). (left :*: right) route -> [Token] Source # gRouteParser :: forall (route :: k). RouteParser ((left :*: right) route) Source # | |
| (GRouter left, GRouter right) => GRouter (left :+: right :: k -> Type) Source # | |
Defined in Miso.Router Methods gFromRoute :: forall (route :: k). (left :+: right) route -> [Token] Source # gRouteParser :: forall (route :: k). RouteParser ((left :+: right) route) Source # | |
| (KnownSymbol name, GRouter next) => GRouter (C1 ('MetaCons name x y) next :: k -> Type) Source # | |
Defined in Miso.Router Methods gFromRoute :: forall (route :: k). C1 ('MetaCons name x y) next route -> [Token] Source # gRouteParser :: forall (route :: k). RouteParser (C1 ('MetaCons name x y) next route) Source # | |
| GRouter next => GRouter (D1 m next :: k -> Type) Source # | |
Defined in Miso.Router Methods gFromRoute :: forall (route :: k). D1 m next route -> [Token] Source # gRouteParser :: forall (route :: k). RouteParser (D1 m next route) Source # | |
| KnownSymbol path => GRouter (K1 m (Path path) :: k -> Type) Source # | |
Defined in Miso.Router Methods gFromRoute :: forall (route :: k). K1 m (Path path) route -> [Token] Source # gRouteParser :: forall (route :: k). RouteParser (K1 m (Path path) route) Source # | |
| KnownSymbol flag => GRouter (K1 m (QueryFlag flag) :: k -> Type) Source # | |
Defined in Miso.Router Methods gFromRoute :: forall (route :: k). K1 m (QueryFlag flag) route -> [Token] Source # gRouteParser :: forall (route :: k). RouteParser (K1 m (QueryFlag flag) route) Source # | |
| (ToMisoString a, FromMisoString a, KnownSymbol param) => GRouter (K1 m (QueryParam param a) :: k -> Type) Source # | |
Defined in Miso.Router Methods gFromRoute :: forall (route :: k). K1 m (QueryParam param a) route -> [Token] Source # gRouteParser :: forall (route :: k). RouteParser (K1 m (QueryParam param a) route) Source # | |
| Router a => GRouter (K1 m a :: k -> Type) Source # | |
Defined in Miso.Router Methods gFromRoute :: forall (route :: k). K1 m a route -> [Token] Source # gRouteParser :: forall (route :: k). RouteParser (K1 m a route) Source # | |
| GRouter next => GRouter (S1 m next :: k -> Type) Source # | |
Defined in Miso.Router Methods gFromRoute :: forall (route :: k). S1 m next route -> [Token] Source # gRouteParser :: forall (route :: k). RouteParser (S1 m next route) Source # | |
| (FromMisoString a, ToMisoString a) => GRouter (K1 m (Capture sym a) :: k2 -> Type) Source # | |
Defined in Miso.Router Methods gFromRoute :: forall (route :: k2). K1 m (Capture sym a) route -> [Token] Source # gRouteParser :: forall (route :: k2). RouteParser (K1 m (Capture sym a) route) Source # | |
Types
newtype Capture (sym :: k) a Source #
Type used for representing capture variables
Constructors
| Capture a |
Instances
| (FromMisoString a, ToMisoString a) => GRouter (K1 m (Capture sym a) :: k2 -> Type) Source # | |
Defined in Miso.Router Methods gFromRoute :: forall (route :: k2). K1 m (Capture sym a) route -> [Token] Source # gRouteParser :: forall (route :: k2). RouteParser (K1 m (Capture sym a) route) Source # | |
| Show a => Show (Capture sym a) Source # | |
| Eq a => Eq (Capture sym a) Source # | |
| FromMisoString a => FromMisoString (Capture sym a) Source # | |
Defined in Miso.Router Methods fromMisoStringEither :: MisoString -> Either String (Capture sym a) Source # | |
| ToMisoString a => ToMisoString (Capture sym a) Source # | |
Defined in Miso.Router Methods toMisoString :: Capture sym a -> MisoString Source # | |
newtype Path (path :: Symbol) Source #
Type used for representing URL paths
Constructors
| Path MisoString |
Instances
| KnownSymbol path => GRouter (K1 m (Path path) :: k -> Type) Source # | |
Defined in Miso.Router Methods gFromRoute :: forall (route :: k). K1 m (Path path) route -> [Token] Source # gRouteParser :: forall (route :: k). RouteParser (K1 m (Path path) route) Source # | |
| IsString (Path path) Source # | |
Defined in Miso.Router Methods fromString :: String -> Path path # | |
| Show (Path path) Source # | |
| Eq (Path path) Source # | |
| ToMisoString (Path path) Source # | |
Defined in Miso.Router Methods toMisoString :: Path path -> MisoString Source # | |
newtype QueryParam (path :: Symbol) a Source #
Type used for representing query parameters
Constructors
| QueryParam (Maybe a) |
Instances
newtype QueryFlag (path :: Symbol) Source #
Type used for representing query flags
Instances
| KnownSymbol flag => GRouter (K1 m (QueryFlag flag) :: k -> Type) Source # | |
Defined in Miso.Router Methods gFromRoute :: forall (route :: k). K1 m (QueryFlag flag) route -> [Token] Source # gRouteParser :: forall (route :: k). RouteParser (K1 m (QueryFlag flag) route) Source # | |
| Show (QueryFlag path) Source # | |
| Eq (QueryFlag path) Source # | |
| KnownSymbol name => ToMisoString (QueryFlag name) Source # | |
Defined in Miso.Router Methods toMisoString :: QueryFlag name -> MisoString Source # | |
A list of tokens are returned from a successful lex of a URI
Constructors
| QueryParamTokens [(MisoString, MisoString)] | |
| QueryParamToken MisoString MisoString | |
| QueryFlagToken MisoString | |
| CaptureOrPathToken MisoString | |
| FragmentToken MisoString | |
| IndexToken |
Instances
| Show Token Source # | |
| Eq Token Source # | |
| ToMisoString Token Source # | |
Defined in Miso.Router Methods toMisoString :: Token -> MisoString Source # | |
Type for dealing with URI. See the official specification
Constructors
| URI | |
Fields | |
Instances
| Show URI Source # | |
| Eq URI Source # | |
| ToMisoString URI Source # | |
Defined in Miso.Types Methods toMisoString :: URI -> MisoString Source # | |
Errors
data RoutingError Source #
An error that can occur during lexing / parsing of a URI into a user-defined data type
Constructors
| ParseError MisoString [Token] | |
| AmbiguousParse MisoString [Token] | |
| LexError MisoString MisoString | |
| LexErrorEOF MisoString | |
| NoParses MisoString |
Instances
| Show RoutingError Source # | |
Defined in Miso.Router Methods showsPrec :: Int -> RoutingError -> ShowS # show :: RoutingError -> String # showList :: [RoutingError] -> ShowS # | |
| Eq RoutingError Source # | |
Defined in Miso.Router | |
Functions
parseURI :: MisoString -> Either MisoString URI Source #
URI parsing
prettyQueryString :: URI -> MisoString Source #
URI query string pretty-printing
Manual Routing
runRouter :: MisoString -> RouteParser route -> Either RoutingError route Source #
Smart constructor for building a RouteParser
data Route = Widget MisoString Int instance Router Route where routeParser = routes [ Widget <$> path "widget" <*> capture ] fromRoute (Widget path value) = [ toPath path, toCapture value ] router :: Router router => RouteParser router router = routes [ Widget <$> path "widget" <*> capture ] > Right (Widget "widget" 10)
routes :: [RouteParser route] -> RouteParser route Source #
Convenience for specifying multiple routes
Construction
toQueryFlag :: MisoString -> Token Source #
Smart constructor for building a QueryFlagToken
toQueryParam :: ToMisoString s => MisoString -> s -> Token Source #
Smart constructor for building a QueryParamToken
toCapture :: ToMisoString string => string -> Token Source #
Smart constructor for building a capture variable
toPath :: MisoString -> Token Source #
Smart constructor for building a path fragment
Parser combinators
queryFlag :: forall (flag :: Symbol). KnownSymbol flag => RouteParser (QueryFlag flag) Source #
Query flag parser from a route
queryParam :: forall (param :: Symbol) a. (FromMisoString a, KnownSymbol param) => RouteParser (QueryParam param a) Source #
Query parameter parser from a route
capture :: FromMisoString value => RouteParser value Source #
Combinator for parsing a capture variable out of a URI
path :: MisoString -> RouteParser MisoString Source #
Combinator for parsing a path out of a URI