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 "widget10" 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
- 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 #
Minimal complete definition
Nothing
Methods
fromRoute :: route -> [Token] Source #
toURI :: route -> URI Source #
route :: URI -> Either RoutingError route Source #
href_ :: route -> Attribute action Source #
prettyRoute :: route -> MisoString Source #
dumpURI :: route -> MisoString Source #
toRoute :: MisoString -> Either RoutingError route Source #
routeParser :: RouteParser route Source #
default routeParser :: (Generic route, GRouter (Rep route)) => RouteParser route Source #
Types
newtype Capture (sym :: k) a Source #
Constructors
Capture a |
Instances
Generic (Capture sym a) Source # | |||||
Defined in Miso.Router Associated Types
| |||||
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 # | |||||
type Rep (Capture sym a) Source # | |||||
Defined in Miso.Router |
newtype Path (path :: Symbol) Source #
Constructors
Path MisoString |
Instances
IsString (Path path) Source # | |||||
Defined in Miso.Router Methods fromString :: String -> Path path # | |||||
Generic (Path path) Source # | |||||
Defined in Miso.Router Associated Types
| |||||
Show (Path path) Source # | |||||
Eq (Path path) Source # | |||||
ToMisoString (Path path) Source # | |||||
Defined in Miso.Router Methods toMisoString :: Path path -> MisoString Source # | |||||
type Rep (Path path) Source # | |||||
Defined in Miso.Router type Rep (Path path) = D1 ('MetaData "Path" "Miso.Router" "miso-1.9.0.0-inplace" 'True) (C1 ('MetaCons "Path" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MisoString))) |
newtype QueryParam (path :: Symbol) a Source #
Constructors
QueryParam (Maybe a) |
Instances
newtype QueryFlag (path :: Symbol) Source #
Instances
Generic (QueryFlag path) Source # | |||||
Defined in Miso.Router Associated Types
| |||||
Show (QueryFlag path) Source # | |||||
Eq (QueryFlag path) Source # | |||||
KnownSymbol name => ToMisoString (QueryFlag name) Source # | |||||
Defined in Miso.Router Methods toMisoString :: QueryFlag name -> MisoString Source # | |||||
type Rep (QueryFlag path) Source # | |||||
Defined in Miso.Router |
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
Constructors
URI | |
Fields |
Instances
Show URI Source # | |
Eq URI Source # | |
ToMisoString URI Source # | |
Defined in Miso.Router Methods toMisoString :: URI -> MisoString Source # |
Errors
data RoutingError Source #
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 #
prettyURI :: URI -> MisoString Source #
prettyQueryString :: URI -> MisoString Source #
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)
Construction
toQueryFlag :: MisoString -> Token Source #
toQueryParam :: ToMisoString s => MisoString -> s -> Token Source #
toCapture :: ToMisoString string => string -> Token Source #
toPath :: MisoString -> Token Source #
Parser combinators
queryParam :: forall (param :: Symbol) a. (FromMisoString a, KnownSymbol param) => RouteParser (QueryParam param a) Source #
capture :: FromMisoString value => RouteParser value Source #
path :: MisoString -> RouteParser MisoString Source #