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 "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

Classes

class Router route where Source #

Minimal complete definition

Nothing

Methods

fromRoute :: route -> [Token] Source #

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

Instances details
Generic (Capture sym a) Source # 
Instance details

Defined in Miso.Router

Associated Types

type Rep (Capture sym a) 
Instance details

Defined in Miso.Router

type Rep (Capture sym a) = D1 ('MetaData "Capture" "Miso.Router" "miso-1.9.0.0-inplace" 'True) (C1 ('MetaCons "Capture" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Capture sym a -> Rep (Capture sym a) x #

to :: Rep (Capture sym a) x -> Capture sym a #

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

type Rep (Capture sym a) Source # 
Instance details

Defined in Miso.Router

type Rep (Capture sym a) = D1 ('MetaData "Capture" "Miso.Router" "miso-1.9.0.0-inplace" 'True) (C1 ('MetaCons "Capture" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

newtype Path (path :: Symbol) Source #

Constructors

Path MisoString 

Instances

Instances details
IsString (Path path) Source # 
Instance details

Defined in Miso.Router

Methods

fromString :: String -> Path path #

Generic (Path path) Source # 
Instance details

Defined in Miso.Router

Associated Types

type Rep (Path path) 
Instance details

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)))

Methods

from :: Path path -> Rep (Path path) x #

to :: Rep (Path path) x -> 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 #

type Rep (Path path) Source # 
Instance details

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

Instances details
Generic (QueryParam path a) Source # 
Instance details

Defined in Miso.Router

Associated Types

type Rep (QueryParam path a) 
Instance details

Defined in Miso.Router

type Rep (QueryParam path a) = D1 ('MetaData "QueryParam" "Miso.Router" "miso-1.9.0.0-inplace" 'True) (C1 ('MetaCons "QueryParam" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe a))))

Methods

from :: QueryParam path a -> Rep (QueryParam path a) x #

to :: Rep (QueryParam path a) x -> QueryParam path a #

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

type Rep (QueryParam path a) Source # 
Instance details

Defined in Miso.Router

type Rep (QueryParam path a) = D1 ('MetaData "QueryParam" "Miso.Router" "miso-1.9.0.0-inplace" 'True) (C1 ('MetaCons "QueryParam" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe a))))

newtype QueryFlag (path :: Symbol) Source #

Constructors

QueryFlag Bool 

Instances

Instances details
Generic (QueryFlag path) Source # 
Instance details

Defined in Miso.Router

Associated Types

type Rep (QueryFlag path) 
Instance details

Defined in Miso.Router

type Rep (QueryFlag path) = D1 ('MetaData "QueryFlag" "Miso.Router" "miso-1.9.0.0-inplace" 'True) (C1 ('MetaCons "QueryFlag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

Methods

from :: QueryFlag path -> Rep (QueryFlag path) x #

to :: Rep (QueryFlag path) x -> QueryFlag path #

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

type Rep (QueryFlag path) Source # 
Instance details

Defined in Miso.Router

type Rep (QueryFlag path) = D1 ('MetaData "QueryFlag" "Miso.Router" "miso-1.9.0.0-inplace" 'True) (C1 ('MetaCons "QueryFlag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

data Token Source #

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

Instances

Instances details
Show URI Source # 
Instance details

Defined in Miso.Router

Methods

showsPrec :: Int -> URI -> ShowS #

show :: URI -> String #

showList :: [URI] -> ShowS #

Eq URI Source # 
Instance details

Defined in Miso.Router

Methods

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

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

ToMisoString URI Source # 
Instance details

Defined in Miso.Router

Errors

Functions

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 #

Construction

toCapture :: ToMisoString string => string -> Token Source #

Parser combinators

queryFlag :: forall (flag :: Symbol). KnownSymbol flag => RouteParser (QueryFlag flag) Source #

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 #