- parseRoutes :: QuasiQuoter
- parseRoutesNoCheck :: QuasiQuoter
- parseRoutesFile :: FilePath -> Q Exp
- parseRoutesFileNoCheck :: FilePath -> Q Exp
- mkYesod :: String -> [Resource] -> Q [Dec]
- mkYesodSub :: String -> Cxt -> [Resource] -> Q [Dec]
- mkYesodData :: String -> [Resource] -> Q [Dec]
- mkYesodSubData :: String -> Cxt -> [Resource] -> Q [Dec]
- mkYesodDispatch :: String -> [Resource] -> Q [Dec]
- mkYesodSubDispatch :: String -> Cxt -> [Resource] -> Q [Dec]
- class SinglePiece s where
- fromSinglePiece :: Text -> Maybe s
- toSinglePiece :: s -> Text
- class MultiPiece s where
- fromMultiPiece :: [Text] -> Maybe s
- toMultiPiece :: s -> [Text]
- type Texts = [Text]
- toWaiApp :: (Yesod y, YesodDispatch y y) => y -> IO Application
- toWaiAppPlain :: (Yesod y, YesodDispatch y y) => y -> IO Application
Quasi-quoted routing
parseRoutes :: QuasiQuoterSource
A quasi-quoter to parse a string into a list of Resource
s. Checks for
overlapping routes, failing if present; use parseRoutesNoCheck
to skip the
checking. See documentation site for details on syntax.
parseRoutesNoCheck :: QuasiQuoterSource
Same as parseRoutes
, but performs no overlap checking.
parseRoutesFile :: FilePath -> Q ExpSource
Generates URL datatype and site function for the given Resource
s. This
is used for creating sites, not subsites. See mkYesodSub
for the latter.
Use parseRoutes
to create the Resource
s.
Generates URL datatype and site function for the given Resource
s. This
is used for creating subsites, not sites. See mkYesod
for the latter.
Use parseRoutes
to create the Resource
s. In general, a subsite is not
executable by itself, but instead provides functionality to
be embedded in other sites.
More fine-grained
mkYesodData :: String -> [Resource] -> Q [Dec]Source
Sometimes, you will want to declare your routes in one file and define
your handlers elsewhere. For example, this is the only way to break up a
monolithic file into smaller parts. Use this function, paired with
mkYesodDispatch
, to do just that.
mkYesodDispatch :: String -> [Resource] -> Q [Dec]Source
See mkYesodData
.
Path pieces
class SinglePiece s where
fromSinglePiece :: Text -> Maybe s
toSinglePiece :: s -> Text
class MultiPiece s where
fromMultiPiece :: [Text] -> Maybe s
toMultiPiece :: s -> [Text]
MultiPiece [String] | |
MultiPiece [Text] | |
MultiPiece [Text] |
Convert to WAI
toWaiApp :: (Yesod y, YesodDispatch y y) => y -> IO ApplicationSource
Convert the given argument into a WAI application, executable with any WAI
handler. This is the same as toWaiAppPlain
, except it includes two
middlewares: GZIP compression and autohead. This is the
recommended approach for most users.
toWaiAppPlain :: (Yesod y, YesodDispatch y y) => y -> IO ApplicationSource
Convert the given argument into a WAI application, executable with any WAI
handler. This differs from toWaiApp
in that it uses no middlewares.