/yesod-persistent/Yesod/Persist/Core.hs

https://github.com/yogsototh/yesod · Haskell · 223 lines · 146 code · 19 blank · 58 comment · 4 complexity · 290e910c95c6fe4ab9fb8a20bf67d030 MD5 · raw file

  1. {-# LANGUAGE ConstraintKinds #-}
  2. {-# LANGUAGE TypeFamilies #-}
  3. {-# LANGUAGE CPP #-}
  4. {-# LANGUAGE FlexibleContexts #-}
  5. {-# LANGUAGE RankNTypes #-}
  6. {-# OPTIONS_GHC -fno-warn-orphans #-}
  7. -- | Defines the core functionality of this package. This package is
  8. -- distinguished from Yesod.Persist in that the latter additionally exports the
  9. -- persistent modules themselves.
  10. module Yesod.Persist.Core
  11. ( YesodPersist (..)
  12. , defaultRunDB
  13. , YesodPersistRunner (..)
  14. , defaultGetDBRunner
  15. , DBRunner (..)
  16. , runDBSource
  17. , respondSourceDB
  18. , YesodDB
  19. , get404
  20. , getBy404
  21. , insert400
  22. , insert400_
  23. ) where
  24. import Database.Persist
  25. import Control.Monad.Trans.Reader (ReaderT, runReaderT)
  26. import Yesod.Core
  27. import Data.Conduit
  28. import Blaze.ByteString.Builder (Builder)
  29. import Data.Pool
  30. import Control.Monad.Trans.Resource
  31. import Control.Exception (throwIO)
  32. import Yesod.Core.Types (HandlerContents (HCError))
  33. import qualified Database.Persist.Sql as SQL
  34. unSqlPersistT :: a -> a
  35. unSqlPersistT = id
  36. type YesodDB site = ReaderT (YesodPersistBackend site) (HandlerFor site)
  37. class Monad (YesodDB site) => YesodPersist site where
  38. type YesodPersistBackend site
  39. -- | Allows you to execute database actions within Yesod Handlers. For databases that support it, code inside the action will run as an atomic transaction.
  40. --
  41. --
  42. -- ==== __Example Usage__
  43. --
  44. -- > userId <- runDB $ do
  45. -- > userId <- insert $ User "username" "email@example.com"
  46. -- > insert_ $ UserPreferences userId True
  47. -- > pure userId
  48. runDB :: YesodDB site a -> HandlerFor site a
  49. -- | Helper for creating 'runDB'.
  50. --
  51. -- Since 1.2.0
  52. defaultRunDB :: PersistConfig c
  53. => (site -> c)
  54. -> (site -> PersistConfigPool c)
  55. -> PersistConfigBackend c (HandlerFor site) a
  56. -> HandlerFor site a
  57. defaultRunDB getConfig getPool f = do
  58. master <- getYesod
  59. Database.Persist.runPool
  60. (getConfig master)
  61. f
  62. (getPool master)
  63. -- |
  64. --
  65. -- Since 1.2.0
  66. class YesodPersist site => YesodPersistRunner site where
  67. -- | This function differs from 'runDB' in that it returns a database
  68. -- runner function, as opposed to simply running a single action. This will
  69. -- usually mean that a connection is taken from a pool and then reused for
  70. -- each invocation. This can be useful for creating streaming responses;
  71. -- see 'runDBSource'.
  72. --
  73. -- It additionally returns a cleanup function to free the connection. If
  74. -- your code finishes successfully, you /must/ call this cleanup to
  75. -- indicate changes should be committed. Otherwise, for SQL backends at
  76. -- least, a rollback will be used instead.
  77. --
  78. -- Since 1.2.0
  79. getDBRunner :: HandlerFor site (DBRunner site, HandlerFor site ())
  80. newtype DBRunner site = DBRunner
  81. { runDBRunner :: forall a. YesodDB site a -> HandlerFor site a
  82. }
  83. -- | Helper for implementing 'getDBRunner'.
  84. --
  85. -- Since 1.2.0
  86. #if MIN_VERSION_persistent(2,5,0)
  87. defaultGetDBRunner :: (SQL.IsSqlBackend backend, YesodPersistBackend site ~ backend)
  88. => (site -> Pool backend)
  89. -> HandlerFor site (DBRunner site, HandlerFor site ())
  90. #else
  91. defaultGetDBRunner :: YesodPersistBackend site ~ SQL.SqlBackend
  92. => (site -> Pool SQL.SqlBackend)
  93. -> HandlerFor site (DBRunner site, HandlerFor site ())
  94. #endif
  95. defaultGetDBRunner getPool = do
  96. pool <- fmap getPool getYesod
  97. let withPrep conn f = f (persistBackend conn) (SQL.connPrepare $ persistBackend conn)
  98. (relKey, (conn, local)) <- allocate
  99. (do
  100. (conn, local) <- takeResource pool
  101. #if MIN_VERSION_persistent(2,9,0)
  102. withPrep conn (\c f -> SQL.connBegin c f Nothing)
  103. #else
  104. withPrep conn SQL.connBegin
  105. #endif
  106. return (conn, local)
  107. )
  108. (\(conn, local) -> do
  109. withPrep conn SQL.connRollback
  110. destroyResource pool local conn)
  111. let cleanup = liftIO $ do
  112. withPrep conn SQL.connCommit
  113. putResource local conn
  114. _ <- unprotect relKey
  115. return ()
  116. return (DBRunner $ \x -> runReaderT (unSqlPersistT x) conn, cleanup)
  117. -- | Like 'runDB', but transforms a @Source@. See 'respondSourceDB' for an
  118. -- example, practical use case.
  119. --
  120. -- Since 1.2.0
  121. runDBSource :: YesodPersistRunner site
  122. => ConduitT () a (YesodDB site) ()
  123. -> ConduitT () a (HandlerFor site) ()
  124. runDBSource src = do
  125. (dbrunner, cleanup) <- lift getDBRunner
  126. transPipe (runDBRunner dbrunner) src
  127. lift cleanup
  128. -- | Extends 'respondSource' to create a streaming database response body.
  129. respondSourceDB :: YesodPersistRunner site
  130. => ContentType
  131. -> ConduitT () (Flush Builder) (YesodDB site) ()
  132. -> HandlerFor site TypedContent
  133. respondSourceDB ctype = respondSource ctype . runDBSource
  134. -- | Get the given entity by ID, or return a 404 not found if it doesn't exist.
  135. #if MIN_VERSION_persistent(2,5,0)
  136. get404 :: (MonadIO m, PersistStoreRead backend, PersistRecordBackend val backend)
  137. => Key val
  138. -> ReaderT backend m val
  139. #else
  140. get404 :: (MonadIO m, PersistStore (PersistEntityBackend val), PersistEntity val)
  141. => Key val
  142. -> ReaderT (PersistEntityBackend val) m val
  143. #endif
  144. get404 key = do
  145. mres <- get key
  146. case mres of
  147. Nothing -> notFound'
  148. Just res -> return res
  149. -- | Get the given entity by unique key, or return a 404 not found if it doesn't
  150. -- exist.
  151. #if MIN_VERSION_persistent(2,5,0)
  152. getBy404 :: (PersistUniqueRead backend, PersistRecordBackend val backend, MonadIO m)
  153. => Unique val
  154. -> ReaderT backend m (Entity val)
  155. #else
  156. getBy404 :: (PersistUnique (PersistEntityBackend val), PersistEntity val, MonadIO m)
  157. => Unique val
  158. -> ReaderT (PersistEntityBackend val) m (Entity val)
  159. #endif
  160. getBy404 key = do
  161. mres <- getBy key
  162. case mres of
  163. Nothing -> notFound'
  164. Just res -> return res
  165. -- | Create a new record in the database, returning an automatically
  166. -- created key, or raise a 400 bad request if a uniqueness constraint
  167. -- is violated.
  168. --
  169. -- @since 1.4.1
  170. #if MIN_VERSION_persistent(2,5,0)
  171. insert400 :: (MonadIO m, PersistUniqueWrite backend, PersistRecordBackend val backend)
  172. => val
  173. -> ReaderT backend m (Key val)
  174. #else
  175. insert400 :: (MonadIO m, PersistUnique (PersistEntityBackend val), PersistEntity val)
  176. => val
  177. -> ReaderT (PersistEntityBackend val) m (Key val)
  178. #endif
  179. insert400 datum = do
  180. conflict <- checkUnique datum
  181. case conflict of
  182. Just unique ->
  183. badRequest' $ map (unHaskellName . fst) $ persistUniqueToFieldNames unique
  184. Nothing -> insert datum
  185. -- | Same as 'insert400', but doesnt return a key.
  186. --
  187. -- @since 1.4.1
  188. #if MIN_VERSION_persistent(2,5,0)
  189. insert400_ :: (MonadIO m, PersistUniqueWrite backend, PersistRecordBackend val backend)
  190. => val
  191. -> ReaderT backend m ()
  192. #else
  193. insert400_ :: (MonadIO m, PersistUnique (PersistEntityBackend val), PersistEntity val)
  194. => val
  195. -> ReaderT (PersistEntityBackend val) m ()
  196. #endif
  197. insert400_ datum = insert400 datum >> return ()
  198. -- | Should be equivalent to @lift . notFound@, but there's an apparent bug in
  199. -- GHC 7.4.2 that leads to segfaults. This is a workaround.
  200. notFound' :: MonadIO m => m a
  201. notFound' = liftIO $ throwIO $ HCError NotFound
  202. -- | Constructed like 'notFound'', and for the same reasons.
  203. badRequest' :: MonadIO m => Texts -> m a
  204. badRequest' = liftIO . throwIO . HCError . InvalidArgs