reroute-0.1.0.0: abstract implementation of typed and untyped web routing

Safe HaskellNone

Web.Routing.SafeRouting

Synopsis

Documentation

data RouteHandle m a Source

Constructors

forall as . RouteHandle (Path as) (HListElim as (m a)) 

newtype HListElim' x ts Source

Constructors

HListElim' 

Fields

flipHListElim :: HListElim ts x
 

data SafeRouter m a Source

Constructors

SafeRouter 

Instances

type family HListElim ts a :: *Source

hListUncurry :: HListElim ts a -> HList ts -> aSource

data Path as whereSource

Constructors

Empty :: Path `[]` 
StaticCons :: Text -> Path as -> Path as 
VarCons :: (PathPiece a, Typeable a) => Path as -> Path (a : as) 

Instances

~ [*] a ([] *) => IsString (Path a) 

data PolyMap x whereSource

Constructors

PMNil :: PolyMap x 
PMCons :: (Typeable a, PathPiece a) => PathMap (a -> x) -> PolyMap x -> PolyMap x 

data Id a Source

Constructors

Id 

Fields

getId :: a
 

castDefType :: (Typeable a, Typeable b) => (a -> c) -> Maybe (b -> c)Source

insertPolyMap :: (Typeable a, PathPiece a) => Path ts -> (a -> HList ts -> x) -> PolyMap x -> PolyMap xSource

lookupPolyMap :: Text -> [Text] -> PolyMap x -> [x]Source

data PathMap x Source

Constructors

PathMap [x] (HashMap Text (PathMap x)) (PolyMap x) 

insertPathMap' :: Path ts -> (HList ts -> x) -> PathMap x -> PathMap xSource

match :: PathMap x -> [Text] -> [x]Source

var :: (Typeable a, PathPiece a) => Path (a : `[]`)Source

A route parameter

type Var a = Path (a : `[]`)Source

static :: String -> Path `[]`Source

A static route piece

root :: Path `[]`Source

The root of a path piece. Use to define a handler for /

(</>) :: Path as -> Path bs -> Path (HAppendList as bs)Source

renderRoute :: Path as -> HList as -> TextSource

renderRoute' :: Path as -> HList as -> [Text]Source

parse :: Path as -> [Text] -> Maybe (HList as)Source