miso
Copyright(C) 2016-2025 David M. Johnson
LicenseBSD3-style (see the file LICENSE)
MaintainerDavid M. Johnson <code@dmj.io>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

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

Classes

class Router route where Source #

Class used to facilitate routing for miso applications

Minimal complete definition

Nothing

Methods

fromRoute :: route -> [Token] Source #

default fromRoute :: (Generic route, GRouter (Rep route)) => 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 #

type RouteParser = ParserT URI [Token] [] Source #

State monad for parsing URI

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

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

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

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

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

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

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

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

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

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

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

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

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

Instances details
(FromMisoString a, ToMisoString a) => GRouter (K1 m (Capture sym a) :: k2 -> Type) Source # 
Instance details

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

Defined in Miso.Router

Methods

showsPrec :: Int -> Capture sym a -> ShowS #

show :: Capture sym a -> String #

showList :: [Capture sym a] -> ShowS #

Eq a => Eq (Capture sym a) Source # 
Instance details

Defined in Miso.Router

Methods

(==) :: Capture sym a -> Capture sym a -> Bool #

(/=) :: Capture sym a -> Capture sym a -> Bool #

FromMisoString a => FromMisoString (Capture sym a) Source # 
Instance details

Defined in Miso.Router

ToMisoString a => ToMisoString (Capture sym a) Source # 
Instance details

Defined in Miso.Router

newtype Path (path :: Symbol) Source #

Type used for representing URL paths

Constructors

Path MisoString 

Instances

Instances details
KnownSymbol path => GRouter (K1 m (Path path) :: k -> Type) Source # 
Instance details

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

Defined in Miso.Router

Methods

fromString :: String -> Path path #

Show (Path path) Source # 
Instance details

Defined in Miso.Router

Methods

showsPrec :: Int -> Path path -> ShowS #

show :: Path path -> String #

showList :: [Path path] -> ShowS #

Eq (Path path) Source # 
Instance details

Defined in Miso.Router

Methods

(==) :: Path path -> Path path -> Bool #

(/=) :: Path path -> Path path -> Bool #

ToMisoString (Path path) Source # 
Instance details

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

Instances details
(ToMisoString a, FromMisoString a, KnownSymbol param) => GRouter (K1 m (QueryParam param a) :: k -> Type) Source # 
Instance details

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 #

Show a => Show (QueryParam path a) Source # 
Instance details

Defined in Miso.Router

Methods

showsPrec :: Int -> QueryParam path a -> ShowS #

show :: QueryParam path a -> String #

showList :: [QueryParam path a] -> ShowS #

Eq a => Eq (QueryParam path a) Source # 
Instance details

Defined in Miso.Router

Methods

(==) :: QueryParam path a -> QueryParam path a -> Bool #

(/=) :: QueryParam path a -> QueryParam path a -> Bool #

(FromMisoString a, KnownSymbol path) => FromMisoString (QueryParam path a) Source # 
Instance details

Defined in Miso.Router

(ToMisoString a, KnownSymbol path) => ToMisoString (QueryParam path a) Source # 
Instance details

Defined in Miso.Router

newtype QueryFlag (path :: Symbol) Source #

Type used for representing query flags

Constructors

QueryFlag Bool 

Instances

Instances details
KnownSymbol flag => GRouter (K1 m (QueryFlag flag) :: k -> Type) Source # 
Instance details

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

Defined in Miso.Router

Methods

showsPrec :: Int -> QueryFlag path -> ShowS #

show :: QueryFlag path -> String #

showList :: [QueryFlag path] -> ShowS #

Eq (QueryFlag path) Source # 
Instance details

Defined in Miso.Router

Methods

(==) :: QueryFlag path -> QueryFlag path -> Bool #

(/=) :: QueryFlag path -> QueryFlag path -> Bool #

KnownSymbol name => ToMisoString (QueryFlag name) Source # 
Instance details

Defined in Miso.Router

data Token Source #

A list of tokens are returned from a successful lex of a URI

Instances

Instances details
Show Token Source # 
Instance details

Defined in Miso.Router

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

Eq Token Source # 
Instance details

Defined in Miso.Router

Methods

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

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

ToMisoString Token Source # 
Instance details

Defined in Miso.Router

data URI Source #

Type for dealing with URI. See the official specification

Instances

Instances details
Show URI Source # 
Instance details

Defined in Miso.Types

Methods

showsPrec :: Int -> URI -> ShowS #

show :: URI -> String #

showList :: [URI] -> ShowS #

Eq URI Source # 
Instance details

Defined in Miso.Types

Methods

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

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

ToMisoString URI Source # 
Instance details

Defined in Miso.Types

Errors

data RoutingError Source #

An error that can occur during lexing / parsing of a URI into a user-defined data type

Instances

Instances details
Show RoutingError Source # 
Instance details

Defined in Miso.Router

Eq RoutingError Source # 
Instance details

Defined in Miso.Router

Functions

prettyURI :: URI -> MisoString Source #

URI pretty-printing

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

emptyURI :: URI Source #

An empty URI

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