Skip to content

Commit

Permalink
Add function to delete by record ID
Browse files Browse the repository at this point in the history
  • Loading branch information
Nick Hamilton committed Dec 2, 2020
1 parent 1e0a12f commit 11639d3
Show file tree
Hide file tree
Showing 2 changed files with 18 additions and 8 deletions.
22 changes: 16 additions & 6 deletions IHP/ModelSupport.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ module IHP.ModelSupport
import IHP.HaskellSupport
import IHP.NameSupport
import qualified Prelude
import ClassyPrelude hiding (UTCTime, find, ModifiedJulianDay)
import ClassyPrelude hiding (UTCTime, find, ModifiedJulianDay, delete)
import qualified ClassyPrelude
import Database.PostgreSQL.Simple (Connection)
import qualified Text.Inflections
Expand Down Expand Up @@ -342,14 +342,24 @@ logQuery query parameters = when queryDebuggingEnabled (putStrLn (tshow (query,
--
-- Use 'deleteRecords' if you want to delete multiple records.
deleteRecord :: forall model id. (?modelContext :: ModelContext, Show id, KnownSymbol (GetTableName model), HasField "id" model id, ToField id) => model -> IO ()
deleteRecord model = do
let id = getField @"id" model
deleteRecord model = get #id model |> delete @model @id

{-# INLINE deleteRecord #-}

-- | Like 'deleteRecord' but using an Id
--
-- >>> let project :: Id Project = ...
-- >>> delete projectId
-- DELETE FROM projects WHERE id = '..'
--
delete :: forall model id. (?modelContext :: ModelContext, Show id, KnownSymbol (GetTableName model), HasField "id" model id, ToField id) => id -> IO ()
delete id = do
let theQuery = "DELETE FROM " <> tableName @model <> " WHERE id = ?"
let theParameters = (PG.Only id)
logQuery theQuery theParameters
sqlExec (PG.Query . cs $! theQuery) theParameters
pure ()
{-# INLINE deleteRecord #-}
{-# INLINE delete #-}

-- | Runs a @DELETE@ query for a list of records.
--
Expand Down Expand Up @@ -588,10 +598,10 @@ trackTableRead tableName = case get #trackTableReadCallback ?modelContext of
-- > withTableReadTracker do
-- > project <- query @Project |> fetchOne
-- > user <- query @User |> fetchOne
-- >
-- >
-- > tables <- readIORef ?touchedTables
-- > -- tables = Set.fromList ["projects", "users"]
-- >
-- >
withTableReadTracker :: (?modelContext :: ModelContext) => ((?modelContext :: ModelContext, ?touchedTables :: IORef (Set Text)) => IO ()) -> IO ()
withTableReadTracker trackedSection = do
touchedTablesVar <- newIORef Set.empty
Expand Down
4 changes: 2 additions & 2 deletions IHP/Prelude.hs
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,7 @@ import qualified Prelude
import qualified Data.Text as Text
import Data.Proxy (Proxy (Proxy))
import Control.Monad (when, unless, mapM, mapM_, forM, forM_, sequence, sequence_, join, forever)
import Data.List hiding (head, last, unwords, unlines, words, lines, isPrefixOf, isSuffixOf, isInfixOf, intercalate, intersperse, (++), splitAt, null)
import Data.List hiding (head, last, unwords, unlines, words, lines, isPrefixOf, isSuffixOf, isInfixOf, intercalate, intersperse, (++), splitAt, null, delete)
import qualified Data.List as List
import Data.String.Conversions (ConvertibleStrings (convertString), cs)
import Data.Time.Clock
Expand Down Expand Up @@ -90,4 +90,4 @@ last list = Just (List.last list)
lastMay :: [a] -> Maybe a
lastMay = last

plain = Data.String.Interpolate.i
plain = Data.String.Interpolate.i

0 comments on commit 11639d3

Please sign in to comment.