/yesod-core/Yesod/Dispatch.hs

https://github.com/bjornbm/yesod · Haskell · 194 lines · 147 code · 22 blank · 25 comment · 7 complexity · 4ec00deffd9ed7e6db52315d404a88eb MD5 · raw file

  1. {-# LANGUAGE TemplateHaskell #-}
  2. {-# LANGUAGE CPP #-}
  3. {-# LANGUAGE OverloadedStrings #-}
  4. module Yesod.Dispatch
  5. ( -- * Quasi-quoted routing
  6. parseRoutes
  7. , parseRoutesFile
  8. , mkYesod
  9. , mkYesodSub
  10. -- ** More fine-grained
  11. , mkYesodData
  12. , mkYesodSubData
  13. , mkYesodDispatch
  14. , mkYesodSubDispatch
  15. -- ** Path pieces
  16. , SinglePiece (..)
  17. , MultiPiece (..)
  18. , Texts
  19. -- * Convert to WAI
  20. , toWaiApp
  21. , toWaiAppPlain
  22. ) where
  23. import Data.Functor ((<$>))
  24. import Data.Either (partitionEithers)
  25. import Prelude hiding (exp)
  26. import Yesod.Internal.Core
  27. import Yesod.Handler
  28. import Yesod.Internal.Dispatch
  29. import Yesod.Widget (GWidget)
  30. import Web.PathPieces (SinglePiece (..), MultiPiece (..))
  31. import Yesod.Internal.RouteParsing (THResource, Pieces (..), createRoutes, createRender, Resource (..), parseRoutes, parseRoutesFile)
  32. import Language.Haskell.TH.Syntax
  33. import qualified Network.Wai as W
  34. import Network.Wai.Middleware.Jsonp
  35. import Network.Wai.Middleware.Gzip
  36. import Network.Wai.Middleware.Autohead
  37. import Data.ByteString.Lazy.Char8 ()
  38. import Web.ClientSession
  39. import Data.Char (isUpper)
  40. import Data.Text (Text)
  41. type Texts = [Text]
  42. -- | Generates URL datatype and site function for the given 'Resource's. This
  43. -- is used for creating sites, /not/ subsites. See 'mkYesodSub' for the latter.
  44. -- Use 'parseRoutes' to create the 'Resource's.
  45. mkYesod :: String -- ^ name of the argument datatype
  46. -> [Resource]
  47. -> Q [Dec]
  48. mkYesod name = fmap (uncurry (++)) . mkYesodGeneral name [] [] False
  49. -- | Generates URL datatype and site function for the given 'Resource's. This
  50. -- is used for creating subsites, /not/ sites. See 'mkYesod' for the latter.
  51. -- Use 'parseRoutes' to create the 'Resource's. In general, a subsite is not
  52. -- executable by itself, but instead provides functionality to
  53. -- be embedded in other sites.
  54. mkYesodSub :: String -- ^ name of the argument datatype
  55. -> Cxt
  56. -> [Resource]
  57. -> Q [Dec]
  58. mkYesodSub name clazzes =
  59. fmap (uncurry (++)) . mkYesodGeneral name' rest clazzes True
  60. where
  61. (name':rest) = words name
  62. -- | Sometimes, you will want to declare your routes in one file and define
  63. -- your handlers elsewhere. For example, this is the only way to break up a
  64. -- monolithic file into smaller parts. Use this function, paired with
  65. -- 'mkYesodDispatch', to do just that.
  66. mkYesodData :: String -> [Resource] -> Q [Dec]
  67. mkYesodData name res = mkYesodDataGeneral name [] False res
  68. mkYesodSubData :: String -> Cxt -> [Resource] -> Q [Dec]
  69. mkYesodSubData name clazzes res = mkYesodDataGeneral name clazzes True res
  70. mkYesodDataGeneral :: String -> Cxt -> Bool -> [Resource] -> Q [Dec]
  71. mkYesodDataGeneral name clazzes isSub res = do
  72. let (name':rest) = words name
  73. (x, _) <- mkYesodGeneral name' rest clazzes isSub res
  74. let rname = mkName $ "resources" ++ name
  75. eres <- lift res
  76. let y = [ SigD rname $ ListT `AppT` ConT ''Resource
  77. , FunD rname [Clause [] (NormalB eres) []]
  78. ]
  79. return $ x ++ y
  80. -- | See 'mkYesodData'.
  81. mkYesodDispatch :: String -> [Resource] -> Q [Dec]
  82. mkYesodDispatch name = fmap snd . mkYesodGeneral name [] [] False
  83. mkYesodSubDispatch :: String -> Cxt -> [Resource] -> Q [Dec]
  84. mkYesodSubDispatch name clazzes = fmap snd . mkYesodGeneral name' rest clazzes True
  85. where (name':rest) = words name
  86. mkYesodGeneral :: String -- ^ foundation name
  87. -> [String] -- ^ parameters for foundation
  88. -> Cxt -- ^ classes
  89. -> Bool -- ^ is subsite?
  90. -> [Resource]
  91. -> Q ([Dec], [Dec])
  92. mkYesodGeneral name args clazzes isSub res = do
  93. let args' = map mkName args
  94. arg = foldl AppT (ConT name') $ map VarT args'
  95. th' <- mapM thResourceFromResource res
  96. let th = map fst th'
  97. w' <- createRoutes th
  98. let routesName = mkName $ name ++ "Route"
  99. let w = DataD [] routesName [] w' [''Show, ''Read, ''Eq]
  100. let x = TySynInstD ''Route [arg] $ ConT routesName
  101. render <- createRender th
  102. let x' = InstanceD [] (ConT ''RenderRoute `AppT` ConT routesName)
  103. [ FunD (mkName "renderRoute") render
  104. ]
  105. let splitter :: (THResource, Maybe String)
  106. -> Either
  107. (THResource, Maybe String)
  108. (THResource, Maybe String)
  109. splitter a@((_, SubSite{}), _) = Left a
  110. splitter a = Right a
  111. let (resSub, resLoc) = partitionEithers $ map splitter th'
  112. yd <- mkYesodDispatch' resSub resLoc
  113. let master = mkName "master"
  114. let ctx = if isSub
  115. then ClassP (mkName "Yesod") [VarT master] : clazzes
  116. else []
  117. let ytyp = if isSub
  118. then ConT ''YesodDispatch `AppT` arg `AppT` VarT master
  119. else ConT ''YesodDispatch `AppT` arg `AppT` arg
  120. let y = InstanceD ctx ytyp [FunD (mkName "yesodDispatch") [yd]]
  121. return ([w, x, x'] ++ masterTypSyns, [y])
  122. where
  123. name' = mkName name
  124. masterTypSyns
  125. | isSub = []
  126. | otherwise =
  127. [ TySynD
  128. (mkName "Handler")
  129. []
  130. (ConT ''GHandler `AppT` ConT name' `AppT` ConT name')
  131. , TySynD
  132. (mkName "Widget")
  133. []
  134. (ConT ''GWidget `AppT` ConT name' `AppT` ConT name' `AppT` TupleT 0)
  135. ]
  136. thResourceFromResource :: Resource -> Q (THResource, Maybe String)
  137. thResourceFromResource (Resource n ps atts)
  138. | all (all isUpper) atts = return ((n, Simple ps atts), Nothing)
  139. thResourceFromResource (Resource n ps [stype, toSubArg]) = do
  140. let stype' = ConT $ mkName stype
  141. parse <- [|error "ssParse"|]
  142. dispatch <- [|error "ssDispatch"|]
  143. render <- [|renderRoute|]
  144. tmg <- [|error "ssToMasterArg"|]
  145. return ((n, SubSite
  146. { ssType = ConT ''Route `AppT` stype'
  147. , ssParse = parse
  148. , ssRender = render
  149. , ssDispatch = dispatch
  150. , ssToMasterArg = tmg
  151. , ssPieces = ps
  152. }), Just toSubArg)
  153. thResourceFromResource (Resource n _ _) =
  154. error $ "Invalid attributes for resource: " ++ n
  155. -- | Convert the given argument into a WAI application, executable with any WAI
  156. -- handler. This is the same as 'toWaiAppPlain', except it includes three
  157. -- middlewares: GZIP compression, JSON-P and path cleaning. This is the
  158. -- recommended approach for most users.
  159. toWaiApp :: (Yesod y, YesodDispatch y y) => y -> IO W.Application
  160. toWaiApp y = gzip False . jsonp . autohead <$> toWaiAppPlain y
  161. -- | Convert the given argument into a WAI application, executable with any WAI
  162. -- handler. This differs from 'toWaiApp' in that it uses no middlewares.
  163. toWaiAppPlain :: (Yesod y, YesodDispatch y y) => y -> IO W.Application
  164. toWaiAppPlain a = toWaiApp' a <$> encryptKey a
  165. toWaiApp' :: (Yesod y, YesodDispatch y y)
  166. => y
  167. -> Maybe Key
  168. -> W.Application
  169. toWaiApp' y key' env =
  170. case yesodDispatch y key' (W.pathInfo env) y id of
  171. Just app -> app env
  172. Nothing -> yesodRunner y y id key' Nothing notFound env